{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
module Lang.Crucible.LLVM.Intrinsics.LLVM where
import GHC.TypeNats (KnownNat)
import Control.Lens hiding (op, (:>), Empty)
import Control.Monad (foldM, unless)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Bits ((.&.))
import qualified Data.Vector as V
import qualified Text.LLVM.AST as L
import qualified Data.BitVector.Sized as BV
import qualified Data.Parameterized.Context as Ctx
import Data.Parameterized.Context ( pattern (:>), pattern Empty )
import What4.Interface
import What4.InterpretedFloatingPoint
import qualified What4.SpecialFunctions as W4
import Lang.Crucible.Backend
import Lang.Crucible.CFG.Common (GlobalVar)
import Lang.Crucible.Types
import Lang.Crucible.Simulator.OverrideSim
import Lang.Crucible.Simulator.RegMap
import Lang.Crucible.Simulator.SimError (SimErrorReason(AssertFailureSimError))
import Lang.Crucible.LLVM.Bytes (Bytes(..), bitsToBytes)
import Lang.Crucible.LLVM.DataLayout (noAlignment)
import Lang.Crucible.LLVM.MemModel
import Lang.Crucible.LLVM.QQ( llvmOvr )
import Lang.Crucible.LLVM.Utils
import Lang.Crucible.LLVM.Intrinsics.Common
import qualified Lang.Crucible.LLVM.Intrinsics.Libc as Libc
import Lang.Crucible.LLVM.TypeContext (TypeContext)
mkNull
:: (IsSymInterface sym, HasPtrWidth wptr)
=> OverrideSim p sym ext rtp args ret (LLVMPtr sym wptr)
mkNull :: forall sym (wptr :: Natural) p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasPtrWidth wptr) =>
OverrideSim p sym ext rtp args ret (LLVMPtr sym wptr)
mkNull = do
sym
sym <- OverrideSim p sym ext rtp args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (LLVMPtr sym wptr)
-> OverrideSim p sym ext rtp args ret (LLVMPtr sym wptr)
forall a. IO a -> OverrideSim p sym ext rtp args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (sym -> NatRepr wptr -> IO (LLVMPtr sym wptr)
forall (w :: Natural) sym.
(1 <= w, IsSymInterface sym) =>
sym -> NatRepr w -> IO (LLVMPtr sym w)
mkNullPointer sym
sym NatRepr wptr
forall (w :: Natural) (w' :: Natural).
(HasPtrWidth w, w ~ w') =>
NatRepr w'
PtrWidth)
basic_llvm_overrides ::
( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?lc :: TypeContext, ?memOpts :: MemOptions ) =>
[SomeLLVMOverride p sym ext]
basic_llvm_overrides :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?lc::TypeContext, ?memOpts::MemOptions) =>
[SomeLLVMOverride p sym ext]
basic_llvm_overrides =
[ LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeStartOverride
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeEndOverride
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (String
-> NatRepr 8
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
forall (width :: Natural) sym (wptr :: Natural) p ext.
(1 <= width, KnownNat width, IsSymInterface sym,
HasPtrWidth wptr) =>
String
-> NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload String
"start" (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8))
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (String
-> NatRepr 8
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
forall (width :: Natural) sym (wptr :: Natural) p ext.
(1 <= width, KnownNat width, IsSymInterface sym,
HasPtrWidth wptr) =>
String
-> NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload String
"end" (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8))
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (String
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
String
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload_opaque String
"start")
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (String
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
String
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload_opaque String
"end")
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 8
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
forall sym (wptr :: Natural) (width :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
llvmInvariantStartOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8))
, LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
llvmInvariantStartOverride_opaque
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 8
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
forall sym (wptr :: Natural) (width :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
NatRepr width
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
llvmInvariantEndOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8))
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
llvmInvariantEndOverride_opaque
, LLVMOverride p sym ext (EmptyCtx ::> BVType 1) UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride p sym ext (EmptyCtx ::> BVType 1) UnitType
forall sym p ext.
IsSymInterface sym =>
LLVMOverride p sym ext (EmptyCtx ::> BVType 1) UnitType
llvmAssumeOverride
, LLVMOverride p sym ext EmptyCtx UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride p sym ext EmptyCtx UnitType
forall sym p ext.
IsSymInterface sym =>
LLVMOverride p sym ext EmptyCtx UnitType
llvmTrapOverride
, LLVMOverride p sym ext (EmptyCtx ::> BVType 8) UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride p sym ext (EmptyCtx ::> BVType 8) UnitType
forall sym p ext.
IsSymInterface sym =>
LLVMOverride p sym ext (EmptyCtx ::> BVType 8) UnitType
llvmUBSanTrapOverride
, LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32_noalign
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32_noalign_opaque
, LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64_noalign
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64_noalign_opaque
, LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32_noalign
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32_noalign_opaque
, LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64_noalign
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64_noalign_opaque
, LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_32
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_32_noalign
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_32_noalign_opaque
, LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_64
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
llvmMemsetOverride_8_64_noalign
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
llvmMemsetOverride_8_64_noalign_opaque
, LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 32)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 32)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32
, LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 64)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 64)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 32)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 32)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32_null
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 64)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 64)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64_null
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32_null_dynamic
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64_null_dynamic
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32_null_dynamic_opaque
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64_null_dynamic_opaque
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
llvmPrefetchOverride
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
llvmPrefetchOverride_opaque
, LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
llvmPrefetchOverride_preLLVM10
, LLVMOverride p sym ext EmptyCtx (LLVMPointerType wptr)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride p sym ext EmptyCtx (LLVMPointerType wptr)
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext EmptyCtx (LLVMPointerType wptr)
llvmStacksave
, LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr) UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr) UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr) UnitType
llvmStackrestore
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (2 * 8)) (BVType (2 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 2
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (2 * 8)) (BVType (2 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @2))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (4 * 8)) (BVType (4 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 4
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (4 * 8)) (BVType (4 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @4))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (6 * 8)) (BVType (6 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 6
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (6 * 8)) (BVType (6 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @6))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (8 * 8)) (BVType (8 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 8
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (8 * 8)) (BVType (8 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (10 * 8)) (BVType (10 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 10
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (10 * 8)) (BVType (10 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @10))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (12 * 8)) (BVType (12 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 12
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (12 * 8)) (BVType (12 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @12))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (14 * 8)) (BVType (14 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 14
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (14 * 8)) (BVType (14 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @14))
, LLVMOverride
p sym ext (EmptyCtx ::> BVType (16 * 8)) (BVType (16 * 8))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr 16
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (16 * 8)) (BVType (16 * 8))
forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @16))
, LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCopysignOverride_F32
, LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCopysignOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFabsF32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFabsF64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCeilOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCeilOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFloorOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFloorOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmSqrtOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmSqrtOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmSinOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmSinOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCosOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCosOverride_F64
, LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmPowOverride_F32
, LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmPowOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmExpOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmExpOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLogOverride_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLogOverride_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmExp2Override_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmExp2Override_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLog2Override_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLog2Override_F64
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLog10Override_F32
, LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLog10Override_F64
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFmaOverride_F32
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFmaOverride_F64
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFmuladdOverride_F32
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFmuladdOverride_F64
, LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
(BVType 1)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
(BVType 1)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
(BVType 1)
llvmIsFpclassOverride_F32
, LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
(BVType 1)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
(BVType 1)
forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
(BVType 1)
llvmIsFpclassOverride_F64
, LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
UnitType
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
UnitType
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
UnitType
llvmX86_SSE2_storeu_dq
, LLVMOverride
p
sym
ext
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
(VectorType (BVType 64))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride LLVMOverride
p
sym
ext
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
(VectorType (BVType 64))
forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
(VectorType (BVType 64))
llvmX86_pclmulqdq
]
newtype Poly1LLVMOverride p sym ext
= Poly1LLVMOverride (forall w. (1 <= w) => NatRepr w -> SomeLLVMOverride p sym ext)
poly1_llvm_overrides ::
( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?lc :: TypeContext, ?memOpts :: MemOptions ) =>
[(String, Poly1LLVMOverride p sym ext)]
poly1_llvm_overrides :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?lc::TypeContext, ?memOpts::MemOptions) =>
[(String, Poly1LLVMOverride p sym ext)]
poly1_llvm_overrides =
[ (String
"llvm.ctlz"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
llvmCtlz NatRepr w
w)
)
, (String
"llvm.cttz"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
llvmCttz NatRepr w
w)
)
, (String
"llvm.ctpop"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
llvmCtpop NatRepr w
w)
)
, (String
"llvm.bitreverse"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
llvmBitreverse NatRepr w
w)
)
, (String
"llvm.abs"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym, HasLLVMAnn sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
llvmAbsOverride NatRepr w
w)
)
, (String
"llvm.fshl"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
llvmFshl NatRepr w
w)
)
, (String
"llvm.fshr"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
llvmFshr NatRepr w
w)
)
, (String
"llvm.expect"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
forall sym (width :: Natural) p ext.
(IsSymInterface sym, 1 <= width) =>
NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType width) ::> BVType width)
(BVType width)
llvmExpectOverride NatRepr w
w)
)
, (String
"llvm.sadd.with.overflow"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmSaddWithOverflow NatRepr w
w)
)
, (String
"llvm.uadd.with.overflow"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmUaddWithOverflow NatRepr w
w)
)
, (String
"llvm.ssub.with.overflow"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmSsubWithOverflow NatRepr w
w)
)
, (String
"llvm.usub.with.overflow"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmUsubWithOverflow NatRepr w
w)
)
, (String
"llvm.smul.with.overflow"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmSmulWithOverflow NatRepr w
w)
)
, (String
"llvm.umul.with.overflow"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmUmulWithOverflow NatRepr w
w)
)
, (String
"llvm.smax"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmSmax NatRepr w
w)
)
, (String
"llvm.smin"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmSmin NatRepr w
w)
)
, (String
"llvm.umax"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmUmax NatRepr w
w)
)
, (String
"llvm.umin"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmUmin NatRepr w
w)
)
, (String
"llvm.load.relative"
, (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall p sym ext.
(forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
Poly1LLVMOverride ((forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext)
-> (forall (w :: Natural).
(1 <= w) =>
NatRepr w -> SomeLLVMOverride p sym ext)
-> Poly1LLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr w
w -> LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
(LLVMPointerType wptr)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
(LLVMPointerType wptr)
forall (w :: Natural) (wptr :: Natural) sym p ext.
(1 <= w, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts::MemOptions) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
(LLVMPointerType wptr)
llvmLoadRelative NatRepr w
w)
)
]
newtype Poly1VecLLVMOverride p sym ext
= Poly1VecLLVMOverride
(forall vecSz intSz
. (1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> SomeLLVMOverride p sym ext)
poly1_vec_llvm_overrides ::
IsSymInterface sym =>
[(String, Poly1VecLLVMOverride p sym ext)]
poly1_vec_llvm_overrides :: forall sym p ext.
IsSymInterface sym =>
[(String, Poly1VecLLVMOverride p sym ext)]
poly1_vec_llvm_overrides =
[ (String
"llvm.vector.reduce.add"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceAdd NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.mul"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceMul NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.and"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceAnd NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.or"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceOr NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.xor"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceXor NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.smax"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceSmax NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.smin"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceSmin NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.umax"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceUmax NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
, (String
"llvm.vector.reduce.umin"
, (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall p sym ext.
(forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
Poly1VecLLVMOverride ((forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext)
-> (forall (vecSz :: Natural) (intSz :: Natural).
(1 <= intSz) =>
NatRepr vecSz -> NatRepr intSz -> SomeLLVMOverride p sym ext)
-> Poly1VecLLVMOverride p sym ext
forall a b. (a -> b) -> a -> b
$ \NatRepr vecSz
vecSz NatRepr intSz
intSz ->
LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
-> SomeLLVMOverride p sym ext
forall p sym ext (args :: Ctx CrucibleType) (ret :: CrucibleType).
LLVMOverride p sym ext args ret -> SomeLLVMOverride p sym ext
SomeLLVMOverride (NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceUmin NatRepr vecSz
vecSz NatRepr intSz
intSz)
)
]
llvmLifetimeStartOverride
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> BVType 64 ::> LLVMPointerType wptr) UnitType
llvmLifetimeStartOverride :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeStartOverride =
[llvmOvr| void @llvm.lifetime.start( i64, i8* ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmLifetimeEndOverride
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> BVType 64 ::> LLVMPointerType wptr) UnitType
llvmLifetimeEndOverride :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeEndOverride =
[llvmOvr| void @llvm.lifetime.end( i64, i8* ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmLifetimeOverrideOverload
:: forall width sym wptr p ext
. ( 1 <= width, KnownNat width
, IsSymInterface sym, HasPtrWidth wptr)
=> String
-> NatRepr width
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType 64 ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload :: forall (width :: Natural) sym (wptr :: Natural) p ext.
(1 <= width, KnownNat width, IsSymInterface sym,
HasPtrWidth wptr) =>
String
-> NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload String
startOrEnd NatRepr width
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.lifetime." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
startOrEnd String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".p0i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (NatRepr width -> Int
forall (n :: Natural). NatRepr n -> Int
widthVal NatRepr width
w)) in
[llvmOvr| void $nm ( i64, #w * ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmLifetimeOverrideOverload_opaque
:: forall sym wptr p ext
. (IsSymInterface sym, HasPtrWidth wptr)
=> String
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType 64 ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
String
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
UnitType
llvmLifetimeOverrideOverload_opaque String
startOrEnd =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.lifetime." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
startOrEnd String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".p0") in
[llvmOvr| void $nm ( i64, ptr ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmInvariantStartOverride
:: (IsSymInterface sym, HasPtrWidth wptr)
=> NatRepr width
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType 64 ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
llvmInvariantStartOverride :: forall sym (wptr :: Natural) (width :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
llvmInvariantStartOverride NatRepr width
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.invariant.start.p0i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (NatRepr width -> Int
forall (n :: Natural). NatRepr n -> Int
widthVal NatRepr width
w)) in
[llvmOvr| {}* $nm ( i64, #w * ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
_args -> OverrideSim
p sym ext rtp args' ret' (RegValue sym (LLVMPointerType wptr))
forall sym (wptr :: Natural) p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasPtrWidth wptr) =>
OverrideSim p sym ext rtp args ret (LLVMPtr sym wptr)
mkNull)
llvmInvariantStartOverride_opaque
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> BVType 64 ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
llvmInvariantStartOverride_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
(LLVMPointerType wptr)
llvmInvariantStartOverride_opaque =
let nm :: Symbol
nm = String -> Symbol
L.Symbol String
"llvm.invariant.start.p0" in
[llvmOvr| {}* $nm ( i64, ptr ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType 64) ::> LLVMPointerType wptr)
_args -> OverrideSim
p sym ext rtp args' ret' (RegValue sym (LLVMPointerType wptr))
forall sym (wptr :: Natural) p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasPtrWidth wptr) =>
OverrideSim p sym ext rtp args ret (LLVMPtr sym wptr)
mkNull)
llvmInvariantEndOverride
:: (IsSymInterface sym, HasPtrWidth wptr)
=> NatRepr width
-> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> BVType 64 ::> LLVMPointerType wptr)
UnitType
llvmInvariantEndOverride :: forall sym (wptr :: Natural) (width :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
NatRepr width
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
llvmInvariantEndOverride NatRepr width
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.invariant.end.p0i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (NatRepr width -> Int
forall (n :: Natural). NatRepr n -> Int
widthVal NatRepr width
w)) in
[llvmOvr| void $nm ( {}*, i64, #w * ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmInvariantEndOverride_opaque
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> BVType 64 ::> LLVMPointerType wptr)
UnitType
llvmInvariantEndOverride_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
UnitType
llvmInvariantEndOverride_opaque =
let nm :: Symbol
nm = String -> Symbol
L.Symbol String
"llvm.invariant.end.p0" in
[llvmOvr| void $nm ( {}*, i64, ptr ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 64)
::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmExpectOverride
:: (IsSymInterface sym, 1 <= width)
=> NatRepr width
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType width ::> BVType width)
(BVType width)
llvmExpectOverride :: forall sym (width :: Natural) p ext.
(IsSymInterface sym, 1 <= width) =>
NatRepr width
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType width) ::> BVType width)
(BVType width)
llvmExpectOverride NatRepr width
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.expect.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (NatRepr width -> Int
forall (n :: Natural). NatRepr n -> Int
widthVal NatRepr width
w)) in
[llvmOvr| #w $nm ( #w, #w ) |]
(\GlobalVar Mem
_ops Assignment
(RegEntry sym) ((EmptyCtx ::> BVType width) ::> BVType width)
args ->
CurryAssignment
((EmptyCtx ::> BVType width) ::> BVType width)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType width)))
-> Assignment
(RegEntry sym) ((EmptyCtx ::> BVType width) ::> BVType width)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType width))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType width) ::> BVType width) f x
-> Assignment f ((EmptyCtx ::> BVType width) ::> BVType width) -> x
Ctx.uncurryAssignment (\RegEntry sym (BVType width)
val RegEntry sym (BVType width)
_ -> RegValue sym (BVType width)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType width))
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (RegEntry sym (BVType width) -> RegValue sym (BVType width)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType width)
val)) Assignment
(RegEntry sym) ((EmptyCtx ::> BVType width) ::> BVType width)
args)
llvmAssumeOverride
:: (IsSymInterface sym)
=> LLVMOverride p sym ext (EmptyCtx ::> BVType 1) UnitType
llvmAssumeOverride :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride p sym ext (EmptyCtx ::> BVType 1) UnitType
llvmAssumeOverride =
[llvmOvr| void @llvm.assume ( i1 ) |]
(\GlobalVar Mem
_ops Assignment (RegEntry sym) (EmptyCtx ::> BVType 1)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmTrapOverride
:: (IsSymInterface sym)
=> LLVMOverride p sym ext EmptyCtx UnitType
llvmTrapOverride :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride p sym ext EmptyCtx UnitType
llvmTrapOverride =
[llvmOvr| void @llvm.trap() |]
(\GlobalVar Mem
_ops Assignment (RegEntry sym) EmptyCtx
_args ->
(forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> (forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall a b. (a -> b) -> a -> b
$ \bak
bak ->
IO (RegValue sym UnitType)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall a. IO a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (RegValue sym UnitType)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> IO (RegValue sym UnitType)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall a b. (a -> b) -> a -> b
$ bak -> SimErrorReason -> IO (RegValue sym UnitType)
forall sym bak a.
IsSymBackend sym bak =>
bak -> SimErrorReason -> IO a
addFailedAssertion bak
bak (SimErrorReason -> IO (RegValue sym UnitType))
-> SimErrorReason -> IO (RegValue sym UnitType)
forall a b. (a -> b) -> a -> b
$ String -> String -> SimErrorReason
AssertFailureSimError String
"llvm.trap() called" String
"")
llvmUBSanTrapOverride ::
IsSymInterface sym =>
LLVMOverride p sym ext (EmptyCtx ::> BVType 8) UnitType
llvmUBSanTrapOverride :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride p sym ext (EmptyCtx ::> BVType 8) UnitType
llvmUBSanTrapOverride =
[llvmOvr| void @llvm.ubsantrap( i8 ) |]
(\GlobalVar Mem
_ops Assignment (RegEntry sym) (EmptyCtx ::> BVType 8)
_args ->
(forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> (forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall a b. (a -> b) -> a -> b
$ \bak
bak ->
IO (RegValue sym UnitType)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall a. IO a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (RegValue sym UnitType)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> IO (RegValue sym UnitType)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall a b. (a -> b) -> a -> b
$ bak -> SimErrorReason -> IO (RegValue sym UnitType)
forall sym bak a.
IsSymBackend sym bak =>
bak -> SimErrorReason -> IO a
addFailedAssertion bak
bak (SimErrorReason -> IO (RegValue sym UnitType))
-> SimErrorReason -> IO (RegValue sym UnitType)
forall a b. (a -> b) -> a -> b
$ String -> String -> SimErrorReason
AssertFailureSimError String
"llvm.ubsantrap() called" String
"")
llvmStacksave
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext EmptyCtx (LLVMPointerType wptr)
llvmStacksave :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext EmptyCtx (LLVMPointerType wptr)
llvmStacksave =
[llvmOvr| i8* @llvm.stacksave() |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) EmptyCtx
_args -> OverrideSim
p sym ext rtp args' ret' (RegValue sym (LLVMPointerType wptr))
forall sym (wptr :: Natural) p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasPtrWidth wptr) =>
OverrideSim p sym ext rtp args ret (LLVMPtr sym wptr)
mkNull)
llvmStackrestore
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr) UnitType
llvmStackrestore :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr) UnitType
llvmStackrestore =
[llvmOvr| void @llvm.stackrestore( i8* ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> LLVMPointerType wptr)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ())
llvmMemmoveOverride_8_8_32
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 32 ::> BVType 32 ::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32 =
[llvmOvr| void @llvm.memmove.p0i8.p0i8.i32( i8*, i8*, i32, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
args ->
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (\RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 32)
len RegEntry sym (BVType 32)
_align RegEntry sym (BVType 1)
v -> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemmove GlobalVar Mem
memOps RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 32)
len RegEntry sym (BVType 1)
v) Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
args)
llvmMemmoveOverride_8_8_32_noalign
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 32 ::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32_noalign :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32_noalign =
[llvmOvr| void @llvm.memmove.p0i8.p0i8.i32( i8*, i8*, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemmove GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args)
llvmMemmoveOverride_8_8_32_noalign_opaque
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 32 ::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32_noalign_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_32_noalign_opaque =
[llvmOvr| void @llvm.memmove.p0.p0.i32( ptr, ptr, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemmove GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args)
llvmMemmoveOverride_8_8_64
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 64 ::> BVType 32 ::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64 =
[llvmOvr| void @llvm.memmove.p0i8.p0i8.i64( i8*, i8*, i64, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
args ->
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (\RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 64)
len RegEntry sym (BVType 32)
_align RegEntry sym (BVType 1)
v -> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemmove GlobalVar Mem
memOps RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 64)
len RegEntry sym (BVType 1)
v) Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
args)
llvmMemmoveOverride_8_8_64_noalign
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 64 ::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64_noalign :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64_noalign =
[llvmOvr| void @llvm.memmove.p0i8.p0i8.i64( i8*, i8*, i64, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemmove GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args)
llvmMemmoveOverride_8_8_64_noalign_opaque
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 64 ::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64_noalign_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemmoveOverride_8_8_64_noalign_opaque =
[llvmOvr| void @llvm.memmove.p0.p0.i64( ptr, ptr, i64, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args ->
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemmove GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args)
llvmMemsetOverride_8_64
:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> BVType 8
::> BVType 64
::> BVType 32
::> BVType 1)
UnitType
llvmMemsetOverride_8_64 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_64 =
[llvmOvr| void @llvm.memset.p0i8.i64( i8*, i8, i64, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
args ->
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (\RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (BVType 8)
val RegEntry sym (BVType 64)
len RegEntry sym (BVType 32)
_align RegEntry sym (BVType 1)
v -> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemset GlobalVar Mem
memOps RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (BVType 8)
val RegEntry sym (BVType 64)
len RegEntry sym (BVType 1)
v) Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 64)
::> BVType 32)
::> BVType 1)
args)
llvmMemsetOverride_8_64_noalign
:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> BVType 8
::> BVType 64
::> BVType 1)
UnitType
llvmMemsetOverride_8_64_noalign :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
llvmMemsetOverride_8_64_noalign =
[llvmOvr| void @llvm.memset.p0i8.i64( i8*, i8, i64, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemset GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
args)
llvmMemsetOverride_8_64_noalign_opaque
:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> BVType 8
::> BVType 64
::> BVType 1)
UnitType
llvmMemsetOverride_8_64_noalign_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
UnitType
llvmMemsetOverride_8_64_noalign_opaque =
[llvmOvr| void @llvm.memset.p0.i64( ptr, i8, i64, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemset GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 64)
::> BVType 1)
args)
llvmMemsetOverride_8_32
:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> BVType 8
::> BVType 32
::> BVType 32
::> BVType 1)
UnitType
llvmMemsetOverride_8_32 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_32 =
[llvmOvr| void @llvm.memset.p0i8.i32( i8*, i8, i32, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
args ->
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (\RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (BVType 8)
val RegEntry sym (BVType 32)
len RegEntry sym (BVType 32)
_align RegEntry sym (BVType 1)
v -> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemset GlobalVar Mem
memOps RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (BVType 8)
val RegEntry sym (BVType 32)
len RegEntry sym (BVType 1)
v) Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8)
::> BVType 32)
::> BVType 32)
::> BVType 1)
args)
llvmMemsetOverride_8_32_noalign
:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> BVType 8
::> BVType 32
::> BVType 1)
UnitType
llvmMemsetOverride_8_32_noalign :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_32_noalign =
[llvmOvr| void @llvm.memset.p0i8.i32( i8*, i8, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemset GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
args)
llvmMemsetOverride_8_32_noalign_opaque
:: (IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> BVType 8
::> BVType 32
::> BVType 1)
UnitType
llvmMemsetOverride_8_32_noalign_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
UnitType
llvmMemsetOverride_8_32_noalign_opaque =
[llvmOvr| void @llvm.memset.p0.i32( ptr, i8, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 8)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemset GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 8) ::> BVType 32)
::> BVType 1)
args)
llvmMemcpyOverride_8_8_32
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 32 ::> BVType 32 ::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32 =
[llvmOvr| void @llvm.memcpy.p0i8.p0i8.i32( i8*, i8*, i32, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
args ->
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (\RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 32)
len RegEntry sym (BVType 32)
_align RegEntry sym (BVType 1)
v -> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemcpy GlobalVar Mem
memOps RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 32)
len RegEntry sym (BVType 1)
v) Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 32)
::> BVType 1)
args)
llvmMemcpyOverride_8_8_32_noalign
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 32 ::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32_noalign :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32_noalign =
[llvmOvr| void @llvm.memcpy.p0i8.p0i8.i32( i8*, i8*, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemcpy GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args)
llvmMemcpyOverride_8_8_32_noalign_opaque
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 32 ::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32_noalign_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_32_noalign_opaque =
[llvmOvr| void @llvm.memcpy.p0.p0.i32( ptr, ptr, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 32)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemcpy GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 32)
::> BVType 1)
args)
llvmMemcpyOverride_8_8_64
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 64 ::> BVType 32 ::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64 =
[llvmOvr| void @llvm.memcpy.p0i8.p0i8.i64( i8*, i8*, i64, i32, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
args ->
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
f
x
-> Assignment
f
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
-> x
Ctx.uncurryAssignment (\RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 64)
len RegEntry sym (BVType 32)
_align RegEntry sym (BVType 1)
v -> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemcpy GlobalVar Mem
memOps RegEntry sym (LLVMPointerType wptr)
dst RegEntry sym (LLVMPointerType wptr)
src RegEntry sym (BVType 64)
len RegEntry sym (BVType 1)
v) Assignment
(RegEntry sym)
(((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 32)
::> BVType 1)
args)
llvmMemcpyOverride_8_8_64_noalign
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 64 ::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64_noalign :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64_noalign =
[llvmOvr| void @llvm.memcpy.p0i8.p0i8.i64( i8*, i8*, i64, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemcpy GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args)
llvmMemcpyOverride_8_8_64_noalign_opaque
:: ( IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> LLVMPointerType wptr
::> BVType 64 ::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64_noalign_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
UnitType
llvmMemcpyOverride_8_8_64_noalign_opaque =
[llvmOvr| void @llvm.memcpy.p0.p0.i64( ptr, ptr, i64, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 64)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) (w :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret ()
Libc.callMemcpy GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> LLVMPointerType wptr)
::> BVType 64)
::> BVType 1)
args)
llvmObjectsizeOverride_32
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1) (BVType 32)
llvmObjectsizeOverride_32 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32 =
[llvmOvr| i32 @llvm.objectsize.i32.p0i8( i8*, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
args -> CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32)))
-> Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) f x
-> Assignment f ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 32
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize GlobalVar Mem
memOps NatRepr 32
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
args)
llvmObjectsizeOverride_32_null
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1 ::> BVType 1) (BVType 32)
llvmObjectsizeOverride_32_null :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32_null =
[llvmOvr| i32 @llvm.objectsize.i32.p0i8( i8*, i1, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
args -> CurryAssignment
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
f
x
-> Assignment
f (((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 32
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null GlobalVar Mem
memOps NatRepr 32
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
args)
llvmObjectsizeOverride_32_null_dynamic
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1 ::> BVType 1 ::> BVType 1) (BVType 32)
llvmObjectsizeOverride_32_null_dynamic :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32_null_dynamic =
[llvmOvr| i32 @llvm.objectsize.i32.p0i8( i8*, i1, i1, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32)))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 32
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null_dynamic GlobalVar Mem
memOps NatRepr 32
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args)
llvmObjectsizeOverride_32_null_dynamic_opaque
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1 ::> BVType 1 ::> BVType 1) (BVType 32)
llvmObjectsizeOverride_32_null_dynamic_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 32)
llvmObjectsizeOverride_32_null_dynamic_opaque =
[llvmOvr| i32 @llvm.objectsize.i32.p0( ptr, i1, i1, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32)))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 32
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 32))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null_dynamic GlobalVar Mem
memOps NatRepr 32
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args)
llvmObjectsizeOverride_64
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1) (BVType 64)
llvmObjectsizeOverride_64 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64 =
[llvmOvr| i64 @llvm.objectsize.i64.p0i8( i8*, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
args -> CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64)))
-> Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) f x
-> Assignment f ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 64
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize GlobalVar Mem
memOps NatRepr 64
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1)
args)
llvmObjectsizeOverride_64_null
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1 ::> BVType 1) (BVType 64)
llvmObjectsizeOverride_64_null :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64_null =
[llvmOvr| i64 @llvm.objectsize.i64.p0i8( i8*, i1, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
args -> CurryAssignment
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
f
x
-> Assignment
f (((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 64
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null GlobalVar Mem
memOps NatRepr 64
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym)
(((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
args)
llvmObjectsizeOverride_64_null_dynamic
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1 ::> BVType 1 ::> BVType 1) (BVType 64)
llvmObjectsizeOverride_64_null_dynamic :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64_null_dynamic =
[llvmOvr| i64 @llvm.objectsize.i64.p0i8( i8*, i1, i1, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64)))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 64
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null_dynamic GlobalVar Mem
memOps NatRepr 64
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args)
llvmObjectsizeOverride_64_null_dynamic_opaque
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext (EmptyCtx ::> LLVMPointerType wptr ::> BVType 1 ::> BVType 1 ::> BVType 1) (BVType 64)
llvmObjectsizeOverride_64_null_dynamic_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(BVType 64)
llvmObjectsizeOverride_64_null_dynamic_opaque =
[llvmOvr| i64 @llvm.objectsize.i64.p0( ptr, i1, i1, i1 ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args -> CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64)))
-> Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
f
x
-> Assignment
f
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr 64
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 64))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null_dynamic GlobalVar Mem
memOps NatRepr 64
forall (n :: Natural). KnownNat n => NatRepr n
knownNat) Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 1) ::> BVType 1)
::> BVType 1)
args)
llvmPrefetchOverride ::
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> BVType 32 ::> BVType 32 ::> BVType 32)
UnitType
llvmPrefetchOverride :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
llvmPrefetchOverride =
[llvmOvr| void @llvm.prefetch.p0i8( i8*, i32, i32, i32 ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ())
llvmPrefetchOverride_opaque ::
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> BVType 32 ::> BVType 32 ::> BVType 32)
UnitType
llvmPrefetchOverride_opaque :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
llvmPrefetchOverride_opaque =
[llvmOvr| void @llvm.prefetch.p0( ptr, i32, i32, i32 ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ())
llvmPrefetchOverride_preLLVM10 ::
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> BVType 32 ::> BVType 32 ::> BVType 32)
UnitType
llvmPrefetchOverride_preLLVM10 :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
UnitType
llvmPrefetchOverride_preLLVM10 =
[llvmOvr| void @llvm.prefetch( i8*, i32, i32, i32 ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((((EmptyCtx ::> LLVMPointerType wptr) ::> BVType 32)
::> BVType 32)
::> BVType 32)
_args -> () -> OverrideSim p sym ext rtp args' ret' ()
forall a. a -> OverrideSim p sym ext rtp args' ret' a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ())
llvmFshl ::
(1 <= w, IsSymInterface sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w ::> BVType w)
(BVType w)
llvmFshl :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
llvmFshl NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.fshl.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm ( #w, #w, #w ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
args -> CurryAssignment
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w) f x
-> Assignment
f (((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
-> x
Ctx.uncurryAssignment (NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callFshl NatRepr w
w) Assignment
(RegEntry sym)
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
args)
llvmFshr ::
(1 <= w, IsSymInterface sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w ::> BVType w)
(BVType w)
llvmFshr :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(BVType w)
llvmFshr NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.fshr.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm ( #w, #w, #w ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
args -> CurryAssignment
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w) f x
-> Assignment
f (((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
-> x
Ctx.uncurryAssignment (NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callFshr NatRepr w
w) Assignment
(RegEntry sym)
(((EmptyCtx ::> BVType w) ::> BVType w) ::> BVType w)
args)
llvmSaddWithOverflow
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(StructType (EmptyCtx ::> BVType w ::> BVType 1))
llvmSaddWithOverflow :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmSaddWithOverflow NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.sadd.with.overflow.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| { #w, i1 } $nm ( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue
sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callSaddWithOverflow GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmUaddWithOverflow
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(StructType (EmptyCtx ::> BVType w ::> BVType 1))
llvmUaddWithOverflow :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmUaddWithOverflow NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.uadd.with.overflow.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| { #w, i1 } $nm ( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue
sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callUaddWithOverflow GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmSsubWithOverflow
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(StructType (EmptyCtx ::> BVType w ::> BVType 1))
llvmSsubWithOverflow :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmSsubWithOverflow NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.ssub.with.overflow.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| { #w, i1 } $nm ( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue
sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callSsubWithOverflow GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmUsubWithOverflow
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(StructType (EmptyCtx ::> BVType w ::> BVType 1))
llvmUsubWithOverflow :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmUsubWithOverflow NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.usub.with.overflow.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| { #w, i1 } $nm ( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue
sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callUsubWithOverflow GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmSmulWithOverflow
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(StructType (EmptyCtx ::> BVType w ::> BVType 1))
llvmSmulWithOverflow :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmSmulWithOverflow NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.smul.with.overflow.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| { #w, i1 } $nm ( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue
sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callSmulWithOverflow GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmUmulWithOverflow
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(StructType (EmptyCtx ::> BVType w ::> BVType 1))
llvmUmulWithOverflow :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> BVType w) ::> BVType w)
(StructType ((EmptyCtx ::> BVType w) ::> BVType 1))
llvmUmulWithOverflow NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.umul.with.overflow.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| { #w, i1 } $nm ( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue
sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(RegValue sym ('StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callUmulWithOverflow GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmUmax ::
(1 <= w, IsSymInterface sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(BVType w)
llvmUmax :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmUmax NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.umax.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callUmax GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmUmin ::
(1 <= w, IsSymInterface sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(BVType w)
llvmUmin :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmUmin NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.umin.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callUmin GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmSmax ::
(1 <= w, IsSymInterface sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(BVType w)
llvmSmax :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmSmax NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.smax.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callSmax GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmSmin ::
(1 <= w, IsSymInterface sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType w)
(BVType w)
llvmSmin :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType w) (BVType w)
llvmSmin NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.smin.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w, #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callSmin GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType w)
args)
llvmCtlz
:: (1 <= w, IsSymInterface sym)
=> NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType 1)
(BVType w)
llvmCtlz :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
llvmCtlz NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.ctlz.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm ( #w, i1 ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType 1) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType 1) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCtlz GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
args)
llvmCttz
:: (1 <= w, IsSymInterface sym)
=> NatRepr w
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType 1)
(BVType w)
llvmCttz :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
llvmCttz NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.cttz.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm ( #w, i1 ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
args -> CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType 1)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType 1) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType 1) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCttz GlobalVar Mem
memOps) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
args)
llvmCtpop
:: (1 <= w, IsSymInterface sym)
=> NatRepr w
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType w)
(BVType w)
llvmCtpop :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
llvmCtpop NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.ctpop.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) (EmptyCtx ::> BVType w)
args -> CurryAssignment
(EmptyCtx ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) (EmptyCtx ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> BVType w) f x
-> Assignment f (EmptyCtx ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCtpop GlobalVar Mem
memOps) Assignment (RegEntry sym) (EmptyCtx ::> BVType w)
args)
llvmBitreverse
:: (1 <= w, IsSymInterface sym)
=> NatRepr w
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType w)
(BVType w)
llvmBitreverse :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> LLVMOverride p sym ext (EmptyCtx ::> BVType w) (BVType w)
llvmBitreverse NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.bitreverse.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w ) |]
(\GlobalVar Mem
memOps Assignment (RegEntry sym) (EmptyCtx ::> BVType w)
args -> CurryAssignment
(EmptyCtx ::> BVType w)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w)))
-> Assignment (RegEntry sym) (EmptyCtx ::> BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> BVType w) f x
-> Assignment f (EmptyCtx ::> BVType w) -> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callBitreverse GlobalVar Mem
memOps) Assignment (RegEntry sym) (EmptyCtx ::> BVType w)
args)
llvmBSwapOverride
:: forall width sym p ext
. ( 1 <= width, IsSymInterface sym)
=> NatRepr width
-> LLVMOverride p sym ext
(EmptyCtx ::> BVType (width * 8))
(BVType (width * 8))
llvmBSwapOverride :: forall (width :: Natural) sym p ext.
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> LLVMOverride
p sym ext (EmptyCtx ::> BVType (width * 8)) (BVType (width * 8))
llvmBSwapOverride NatRepr width
widthRepr =
let width8 :: NatRepr (width * 8)
width8 = NatRepr width -> NatRepr 8 -> NatRepr (width * 8)
forall (n :: Natural) (m :: Natural).
NatRepr n -> NatRepr m -> NatRepr (n * m)
natMultiply NatRepr width
widthRepr (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8)
nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.bswap.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (NatRepr (width * 8) -> Int
forall (n :: Natural). NatRepr n -> Int
widthVal NatRepr (width * 8)
width8))
in
case NatRepr width -> NatRepr 8 -> (width * 8) :~: (8 * width)
forall (f :: Natural -> Type) (m :: Natural) (g :: Natural -> Type)
(n :: Natural).
f m -> g n -> (m * n) :~: (n * m)
mulComm NatRepr width
widthRepr (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8) of { (width * 8) :~: (8 * width)
Refl ->
case NatRepr 8 -> NatRepr width -> LeqProof width (8 * width)
forall (x :: Natural) (p :: Natural -> Type) (q :: Natural -> Type)
(y :: Natural).
(1 <= x) =>
p x -> q y -> LeqProof y (x * y)
leqMulMono (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @8) NatRepr width
widthRepr :: LeqProof width (width * 8) of { LeqProof width (width * 8)
LeqProof ->
case LeqProof 1 width
-> LeqProof width (width * 8) -> LeqProof 1 (width * 8)
forall (m :: Natural) (n :: Natural) (p :: Natural).
LeqProof m n -> LeqProof n p -> LeqProof m p
leqTrans (LeqProof 1 width
forall (m :: Natural) (n :: Natural). (m <= n) => LeqProof m n
LeqProof :: LeqProof 1 width)
(LeqProof width (width * 8)
forall (m :: Natural) (n :: Natural). (m <= n) => LeqProof m n
LeqProof :: LeqProof width (width * 8)) of { LeqProof 1 (width * 8)
LeqProof ->
[llvmOvr| #width8 $nm( #width8 ) |]
(\GlobalVar Mem
_ Assignment (RegEntry sym) (EmptyCtx ::> BVType (width * 8))
args -> CurryAssignment
(EmptyCtx ::> BVType (width * 8))
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType (width * 8))))
-> Assignment (RegEntry sym) (EmptyCtx ::> BVType (width * 8))
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType (width * 8)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> BVType (width * 8)) f x
-> Assignment f (EmptyCtx ::> BVType (width * 8)) -> x
Ctx.uncurryAssignment (NatRepr width
-> RegEntry sym (BVType (width * 8))
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType (width * 8)))
forall (width :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= width, IsSymInterface sym) =>
NatRepr width
-> RegEntry sym (BVType (width * 8))
-> OverrideSim
p sym ext r args ret (RegValue sym (BVType (width * 8)))
Libc.callBSwap NatRepr width
widthRepr) Assignment (RegEntry sym) (EmptyCtx ::> BVType (width * 8))
args)
}}}
llvmLoadRelative ::
( 1 <= w
, HasPtrWidth wptr
, HasLLVMAnn sym
, ?memOpts :: MemOptions
) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr ::> BVType w)
(LLVMPointerType wptr)
llvmLoadRelative :: forall (w :: Natural) (wptr :: Natural) sym p ext.
(1 <= w, HasPtrWidth wptr, HasLLVMAnn sym, ?memOpts::MemOptions) =>
NatRepr w
-> LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
(LLVMPointerType wptr)
llvmLoadRelative NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.load.relative.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| ptr $nm( ptr, #w ) |]
(\GlobalVar Mem
mvar Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
args -> CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (LLVMPointerType wptr)))
-> Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (LLVMPointerType wptr))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w) f x
-> Assignment f ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (LLVMPointerType wptr))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym, HasPtrWidth wptr, HasLLVMAnn sym,
?memOpts::MemOptions) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (LLVMPtr sym wptr)
callLoadRelative GlobalVar Mem
mvar NatRepr w
w) Assignment
(RegEntry sym) ((EmptyCtx ::> LLVMPointerType wptr) ::> BVType w)
args)
llvmAbsOverride ::
(1 <= w, IsSymInterface sym, HasLLVMAnn sym) =>
NatRepr w ->
LLVMOverride p sym ext
(EmptyCtx ::> BVType w ::> BVType 1)
(BVType w)
llvmAbsOverride :: forall (w :: Natural) sym p ext.
(1 <= w, IsSymInterface sym, HasLLVMAnn sym) =>
NatRepr w
-> LLVMOverride
p sym ext ((EmptyCtx ::> BVType w) ::> BVType 1) (BVType w)
llvmAbsOverride NatRepr w
w =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.abs.i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr w
w)) in
[llvmOvr| #w $nm( #w, i1 ) |]
(\GlobalVar Mem
mvar Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
args ->
do CallStack
callStack <- GlobalVar Mem -> OverrideSim p sym ext rtp args' ret' CallStack
forall p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
GlobalVar Mem -> OverrideSim p sym ext r args ret CallStack
callStackFromMemVar' GlobalVar Mem
mvar
CurryAssignment
((EmptyCtx ::> BVType w) ::> BVType 1)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (SymExpr sym ('BaseBVType w)))
-> Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
-> OverrideSim
p sym ext rtp args' ret' (SymExpr sym ('BaseBVType w))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment ((EmptyCtx ::> BVType w) ::> BVType 1) f x
-> Assignment f ((EmptyCtx ::> BVType w) ::> BVType 1) -> x
Ctx.uncurryAssignment (CallStack
-> NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType w))
forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym, HasLLVMAnn sym) =>
CallStack
-> NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
Libc.callLLVMAbs CallStack
callStack NatRepr w
w) Assignment (RegEntry sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
args)
llvmCopysignOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCopysignOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCopysignOverride_F32 =
[llvmOvr| float @llvm.copysign.f32( float, float ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
args -> CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
f
x
-> Assignment
f ((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
-> x
Ctx.uncurryAssignment CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
callCopysign Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
args)
llvmCopysignOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCopysignOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCopysignOverride_F64 =
[llvmOvr| double @llvm.copysign.f64( double, double ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
args -> CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
f
x
-> Assignment
f ((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
-> x
Ctx.uncurryAssignment CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
callCopysign Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
args)
llvmFabsF32
:: forall sym p ext
. ( IsSymInterface sym)
=> LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFabsF32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFabsF32 =
[llvmOvr| float @llvm.fabs.f32( float ) |]
(\GlobalVar Mem
_memOps (Assignment (RegEntry sym) ctx
Empty :> (RegEntry sym tp -> RegValue sym tp
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym tp
x)) -> do
sym
sym <- OverrideSim p sym ext rtp args' ret' sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym (SymInterpretedFloatType sym SingleFloat))
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(SymExpr sym (SymInterpretedFloatType sym SingleFloat))
forall a. IO a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym
-> SymInterpretedFloat sym fi -> IO (SymInterpretedFloat sym fi)
iFloatAbs @_ @SingleFloat sym
sym RegValue sym tp
SymExpr sym (SymInterpretedFloatType sym SingleFloat)
x))
llvmFabsF64
:: forall sym p ext
. ( IsSymInterface sym)
=> LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFabsF64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFabsF64 =
[llvmOvr| double @llvm.fabs.f64( double ) |]
(\GlobalVar Mem
_memOps (Assignment (RegEntry sym) ctx
Empty :> (RegEntry sym tp -> RegValue sym tp
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym tp
x)) -> do
sym
sym <- OverrideSim p sym ext rtp args' ret' sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym (SymInterpretedFloatType sym DoubleFloat))
-> OverrideSim
p
sym
ext
rtp
args'
ret'
(SymExpr sym (SymInterpretedFloatType sym DoubleFloat))
forall a. IO a -> OverrideSim p sym ext rtp args' ret' a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym
-> SymInterpretedFloat sym fi -> IO (SymInterpretedFloat sym fi)
iFloatAbs @_ @DoubleFloat sym
sym RegValue sym tp
SymExpr sym (SymInterpretedFloatType sym DoubleFloat)
x))
llvmCeilOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCeilOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCeilOverride_F32 =
[llvmOvr| float @llvm.ceil.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callCeil Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmCeilOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCeilOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCeilOverride_F64 =
[llvmOvr| double @llvm.ceil.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callCeil Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmFloorOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFloorOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFloorOverride_F32 =
[llvmOvr| float @llvm.floor.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callFloor Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmFloorOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFloorOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFloorOverride_F64 =
[llvmOvr| double @llvm.floor.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callFloor Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmSqrtOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmSqrtOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmSqrtOverride_F32 =
[llvmOvr| float @llvm.sqrt.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSqrt Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmSqrtOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmSqrtOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmSqrtOverride_F64 =
[llvmOvr| double @llvm.sqrt.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSqrt Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmSinOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmSinOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmSinOverride_F32 =
[llvmOvr| float @llvm.sin.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Sin) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmSinOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmSinOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmSinOverride_F64 =
[llvmOvr| double @llvm.sin.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Sin) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmCosOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCosOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmCosOverride_F32 =
[llvmOvr| float @llvm.cos.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Cos) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmCosOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCosOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmCosOverride_F64 =
[llvmOvr| double @llvm.cos.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Cos) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmPowOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmPowOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmPowOverride_F32 =
[llvmOvr| float @llvm.pow.f32( float, float ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
args -> CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
f
x
-> Assignment
f ((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
-> x
Ctx.uncurryAssignment (SpecialFunction ((EmptyCtx ::> R) ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction ((EmptyCtx ::> R) ::> R)
-> RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction2 SpecialFunction ((EmptyCtx ::> R) ::> R)
W4.Pow) Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
args)
llvmPowOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmPowOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmPowOverride_F64 =
[llvmOvr| double @llvm.pow.f64( double, double ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
args -> CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
f
x
-> Assignment
f ((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
-> x
Ctx.uncurryAssignment (SpecialFunction ((EmptyCtx ::> R) ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction ((EmptyCtx ::> R) ::> R)
-> RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction2 SpecialFunction ((EmptyCtx ::> R) ::> R)
W4.Pow) Assignment
(RegEntry sym)
((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
args)
llvmExpOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmExpOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmExpOverride_F32 =
[llvmOvr| float @llvm.exp.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Exp) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmExpOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmExpOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmExpOverride_F64 =
[llvmOvr| double @llvm.exp.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Exp) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmLogOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLogOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLogOverride_F32 =
[llvmOvr| float @llvm.log.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Log) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmLogOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLogOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLogOverride_F64 =
[llvmOvr| double @llvm.log.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Log) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmExp2Override_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmExp2Override_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmExp2Override_F32 =
[llvmOvr| float @llvm.exp2.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Exp2) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmExp2Override_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmExp2Override_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmExp2Override_F64 =
[llvmOvr| double @llvm.exp2.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Exp2) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmLog2Override_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLog2Override_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLog2Override_F32 =
[llvmOvr| float @llvm.log2.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Log2) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmLog2Override_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLog2Override_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLog2Override_F64 =
[llvmOvr| double @llvm.log2.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Log2) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmLog10Override_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLog10Override_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmLog10Override_F32 =
[llvmOvr| float @llvm.log10.f32( float ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType SingleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType SingleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Log10) Assignment (RegEntry sym) (EmptyCtx ::> FloatType SingleFloat)
args)
llvmLog10Override_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLog10Override_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(EmptyCtx ::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmLog10Override_F64 =
[llvmOvr| double @llvm.log10.f64( double ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args -> CurryAssignment
(EmptyCtx ::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> FloatType DoubleFloat) f x
-> Assignment f (EmptyCtx ::> FloatType DoubleFloat) -> x
Ctx.uncurryAssignment (SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, KnownRepr FloatInfoRepr fi) =>
SpecialFunction (EmptyCtx ::> R)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callSpecialFunction1 SpecialFunction (EmptyCtx ::> R)
W4.Log10) Assignment (RegEntry sym) (EmptyCtx ::> FloatType DoubleFloat)
args)
llvmIsFpclassOverride_F32 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat
::> BVType 32)
(BVType 1)
llvmIsFpclassOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
(BVType 1)
llvmIsFpclassOverride_F32 =
[llvmOvr| i1 @llvm.is.fpclass.f32( float, i32 ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym) ((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
args -> CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1)))
-> Assignment
(RegEntry sym) ((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32) f x
-> Assignment
f ((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
-> x
Ctx.uncurryAssignment CurryAssignment
((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1)))
RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (BVType 32)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (BVType 32)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType 1))
callIsFpclass Assignment
(RegEntry sym) ((EmptyCtx ::> FloatType SingleFloat) ::> BVType 32)
args)
llvmIsFpclassOverride_F64 ::
IsSymInterface sym =>
LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat
::> BVType 32)
(BVType 1)
llvmIsFpclassOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
(BVType 1)
llvmIsFpclassOverride_F64 =
[llvmOvr| i1 @llvm.is.fpclass.f64( double, i32 ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym) ((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
args -> CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1)))
-> Assignment
(RegEntry sym) ((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32) f x
-> Assignment
f ((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
-> x
Ctx.uncurryAssignment CurryAssignment
((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1)))
RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (BVType 32)
-> OverrideSim p sym ext rtp args' ret' (RegValue sym (BVType 1))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (BVType 32)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType 1))
callIsFpclass Assignment
(RegEntry sym) ((EmptyCtx ::> FloatType DoubleFloat) ::> BVType 32)
args)
llvmFmaOverride_F32 ::
forall sym p ext
. IsSymInterface sym
=> LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat
::> FloatType SingleFloat
::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFmaOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFmaOverride_F32 =
[llvmOvr| float @llvm.fma.f32( float, float, float ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
args -> CurryAssignment
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
f
x
-> Assignment
f
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
-> x
Ctx.uncurryAssignment CurryAssignment
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callFMA Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
args)
llvmFmaOverride_F64 ::
forall sym p ext
. IsSymInterface sym
=> LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat
::> FloatType DoubleFloat
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFmaOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFmaOverride_F64 =
[llvmOvr| double @llvm.fma.f64( double, double, double ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
args -> CurryAssignment
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
f
x
-> Assignment
f
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
-> x
Ctx.uncurryAssignment CurryAssignment
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callFMA Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
args)
llvmFmuladdOverride_F32 ::
forall sym p ext
. IsSymInterface sym
=> LLVMOverride p sym ext
(EmptyCtx ::> FloatType SingleFloat
::> FloatType SingleFloat
::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFmuladdOverride_F32 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(FloatType SingleFloat)
llvmFmuladdOverride_F32 =
[llvmOvr| float @llvm.fmuladd.f32( float, float, float ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
args -> CurryAssignment
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
f
x
-> Assignment
f
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
-> x
Ctx.uncurryAssignment CurryAssignment
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat)))
RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (FloatType SingleFloat)
-> RegEntry sym (FloatType SingleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType SingleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callFMA Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType SingleFloat) ::> FloatType SingleFloat)
::> FloatType SingleFloat)
args)
llvmFmuladdOverride_F64 ::
forall sym p ext
. IsSymInterface sym
=> LLVMOverride p sym ext
(EmptyCtx ::> FloatType DoubleFloat
::> FloatType DoubleFloat
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFmuladdOverride_F64 :: forall sym p ext.
IsSymInterface sym =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(FloatType DoubleFloat)
llvmFmuladdOverride_F64 =
[llvmOvr| double @llvm.fmuladd.f64( double, double, double ) |]
(\GlobalVar Mem
_memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
args -> CurryAssignment
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
f
x
-> Assignment
f
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
-> x
Ctx.uncurryAssignment CurryAssignment
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat)))
RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (FloatType DoubleFloat)
-> RegEntry sym (FloatType DoubleFloat)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (FloatType DoubleFloat))
forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
Libc.callFMA Assignment
(RegEntry sym)
(((EmptyCtx ::> FloatType DoubleFloat) ::> FloatType DoubleFloat)
::> FloatType DoubleFloat)
args)
llvmX86_pclmulqdq
:: (IsSymInterface sym, HasPtrWidth wptr)
=> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType 64)
::> VectorType (BVType 64)
::> BVType 8)
(VectorType (BVType 64))
llvmX86_pclmulqdq :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasPtrWidth wptr) =>
LLVMOverride
p
sym
ext
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
(VectorType (BVType 64))
llvmX86_pclmulqdq =
[llvmOvr| <2 x i64> @llvm.x86.pclmulqdq(<2 x i64>, <2 x i64>, i8) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
args -> CurryAssignment
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (VectorType (BVType 64))))
-> Assignment
(RegEntry sym)
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (VectorType (BVType 64)))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
f
x
-> Assignment
f
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (VectorType (BVType 64))
-> RegEntry sym (VectorType (BVType 64))
-> RegEntry sym (BVType 8)
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (VectorType (BVType 64)))
forall p sym ext (wptr :: Natural) r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (VectorType (BVType 64))
-> RegEntry sym (VectorType (BVType 64))
-> RegEntry sym (BVType 8)
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64)))
callX86_pclmulqdq GlobalVar Mem
memOps) Assignment
(RegEntry sym)
(((EmptyCtx ::> VectorType (BVType 64)) ::> VectorType (BVType 64))
::> BVType 8)
args)
llvmX86_SSE2_storeu_dq
:: ( IsSymInterface sym
, HasLLVMAnn sym
, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> LLVMOverride p sym ext
(EmptyCtx ::> LLVMPointerType wptr
::> VectorType (BVType 8))
UnitType
llvmX86_SSE2_storeu_dq :: forall sym (wptr :: Natural) p ext.
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
LLVMOverride
p
sym
ext
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
UnitType
llvmX86_SSE2_storeu_dq =
[llvmOvr| void @llvm.x86.sse2.storeu.dq( i8*, <16 x i8> ) |]
(\GlobalVar Mem
memOps Assignment
(RegEntry sym)
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
args -> CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
(RegEntry sym)
(OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType))
-> Assignment
(RegEntry sym)
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
-> OverrideSim p sym ext rtp args' ret' (RegValue sym UnitType)
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8)) f x
-> Assignment
f ((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
-> x
Ctx.uncurryAssignment (GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (VectorType (BVType 8))
-> OverrideSim p sym ext rtp args' ret' ()
forall sym (wptr :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (VectorType (BVType 8))
-> OverrideSim p sym ext r args ret ()
callStoreudq GlobalVar Mem
memOps) Assignment
(RegEntry sym)
((EmptyCtx ::> LLVMPointerType wptr) ::> VectorType (BVType 8))
args)
llvmVectorReduce ::
(1 <= intSz)
=> String
-> (forall r args ret
. IsSymInterface sym
=> NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduce :: forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
opName forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callReduce NatRepr vecSz
vecSz NatRepr intSz
intSz =
let nm :: Symbol
nm = String -> Symbol
L.Symbol (String
"llvm.vector.reduce." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opName String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
".v" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr vecSz -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr vecSz
vecSz) String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
"i" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr intSz -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue NatRepr intSz
intSz)) in
[llvmOvr| #intSz $nm( <#vecSz x #intSz> ) |]
(\GlobalVar Mem
_memOps Assignment (RegEntry sym) (EmptyCtx ::> VectorType (BVType intSz))
args -> CurryAssignment
(EmptyCtx ::> VectorType (BVType intSz))
(RegEntry sym)
(OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType intSz)))
-> Assignment
(RegEntry sym) (EmptyCtx ::> VectorType (BVType intSz))
-> OverrideSim
p sym ext rtp args' ret' (RegValue sym (BVType intSz))
forall k (ctx :: Ctx k) (f :: k -> Type) x.
CurryAssignmentClass ctx =>
CurryAssignment ctx f x -> Assignment f ctx -> x
forall (f :: CrucibleType -> Type) x.
CurryAssignment (EmptyCtx ::> VectorType (BVType intSz)) f x
-> Assignment f (EmptyCtx ::> VectorType (BVType intSz)) -> x
Ctx.uncurryAssignment (NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext rtp args' ret' (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callReduce NatRepr intSz
intSz) Assignment (RegEntry sym) (EmptyCtx ::> VectorType (BVType intSz))
args)
llvmVectorReduceAdd ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceAdd :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceAdd = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"add" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceAdd
llvmVectorReduceMul ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceMul :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceMul = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"mul" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceMul
llvmVectorReduceAnd ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceAnd :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceAnd = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"and" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceAnd
llvmVectorReduceOr ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceOr :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceOr = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"or" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceOr
llvmVectorReduceXor ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceXor :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceXor = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"xor" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceXor
llvmVectorReduceSmax ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceSmax :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceSmax = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"smax" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceSmax
llvmVectorReduceSmin ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceSmin :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceSmin = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"smin" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceSmin
llvmVectorReduceUmax ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceUmax :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceUmax = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"umax" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceUmax
llvmVectorReduceUmin ::
(1 <= intSz)
=> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride p sym ext
(EmptyCtx ::> VectorType (BVType intSz))
(BVType intSz)
llvmVectorReduceUmin :: forall (intSz :: Natural) (vecSz :: Natural) p sym ext.
(1 <= intSz) =>
NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduceUmin = String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
forall (intSz :: Natural) sym p ext (vecSz :: Natural).
(1 <= intSz) =>
String
-> (forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> NatRepr vecSz
-> NatRepr intSz
-> LLVMOverride
p sym ext (EmptyCtx ::> VectorType (BVType intSz)) (BVType intSz)
llvmVectorReduce String
"umin" NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall r (args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceUmin
callX86_pclmulqdq :: forall p sym ext wptr r args ret.
(IsSymInterface sym, HasPtrWidth wptr) =>
GlobalVar Mem ->
RegEntry sym (VectorType (BVType 64)) ->
RegEntry sym (VectorType (BVType 64)) ->
RegEntry sym (BVType 8) ->
OverrideSim p sym ext r args ret (RegValue sym (VectorType (BVType 64)))
callX86_pclmulqdq :: forall p sym ext (wptr :: Natural) r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasPtrWidth wptr) =>
GlobalVar Mem
-> RegEntry sym (VectorType (BVType 64))
-> RegEntry sym (VectorType (BVType 64))
-> RegEntry sym (BVType 8)
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64)))
callX86_pclmulqdq GlobalVar Mem
_mvar
(RegEntry sym (VectorType (BVType 64))
-> RegValue sym (VectorType (BVType 64))
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (VectorType (BVType 64))
xs)
(RegEntry sym (VectorType (BVType 64))
-> RegValue sym (VectorType (BVType 64))
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (VectorType (BVType 64))
ys)
(RegEntry sym (BVType 8) -> RegValue sym (BVType 8)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType 8)
imm) =
(forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64))))
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64)))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64))))
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64))))
-> (forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64))))
-> OverrideSim
p sym ext r args ret (RegValue sym (VectorType (BVType 64)))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> do
Bool
-> OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless (Vector (SymExpr sym ('BaseBVType 64)) -> Int
forall a. Vector a -> Int
V.length Vector (SymExpr sym ('BaseBVType 64))
RegValue sym (VectorType (BVType 64))
xs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2) (OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ())
-> OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$
IO () -> OverrideSim p sym ext r args ret ()
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> OverrideSim p sym ext r args ret ())
-> IO () -> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$ bak -> SimErrorReason -> IO ()
forall sym bak a.
IsSymBackend sym bak =>
bak -> SimErrorReason -> IO a
addFailedAssertion bak
bak (SimErrorReason -> IO ()) -> SimErrorReason -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String -> SimErrorReason
AssertFailureSimError
(String
"Vector length mismatch in llvm.x86.pclmulqdq intrinsic")
([String] -> String
unwords [String
"Expected <2 x i64>, but got vector of length", Int -> String
forall a. Show a => a -> String
show (Vector (SymExpr sym ('BaseBVType 64)) -> Int
forall a. Vector a -> Int
V.length Vector (SymExpr sym ('BaseBVType 64))
RegValue sym (VectorType (BVType 64))
xs)])
Bool
-> OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless (Vector (SymExpr sym ('BaseBVType 64)) -> Int
forall a. Vector a -> Int
V.length Vector (SymExpr sym ('BaseBVType 64))
RegValue sym (VectorType (BVType 64))
ys Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2) (OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ())
-> OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$
IO () -> OverrideSim p sym ext r args ret ()
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> OverrideSim p sym ext r args ret ())
-> IO () -> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$ bak -> SimErrorReason -> IO ()
forall sym bak a.
IsSymBackend sym bak =>
bak -> SimErrorReason -> IO a
addFailedAssertion bak
bak (SimErrorReason -> IO ()) -> SimErrorReason -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String -> SimErrorReason
AssertFailureSimError
(String
"Vector length mismatch in llvm.x86.pclmulqdq intrinsic")
([String] -> String
unwords [String
"Expected <2 x i64>, but got vector of length", Int -> String
forall a. Show a => a -> String
show (Vector (SymExpr sym ('BaseBVType 64)) -> Int
forall a. Vector a -> Int
V.length Vector (SymExpr sym ('BaseBVType 64))
RegValue sym (VectorType (BVType 64))
ys)])
case BV 8 -> Integer
forall (w :: Natural). BV w -> Integer
BV.asUnsigned (BV 8 -> Integer) -> Maybe (BV 8) -> Maybe Integer
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> SymExpr sym (BaseBVType 8) -> Maybe (BV 8)
forall (w :: Natural). SymExpr sym (BaseBVType w) -> Maybe (BV w)
forall (e :: BaseType -> Type) (w :: Natural).
IsExpr e =>
e (BaseBVType w) -> Maybe (BV w)
asBV RegValue sym (BVType 8)
SymExpr sym (BaseBVType 8)
imm of
Just Integer
byte ->
do let xidx :: Int
xidx = if Integer
byte Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
0x01 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 then Int
0 else Int
1
let yidx :: Int
yidx = if Integer
byte Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
.&. Integer
0x10 Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 then Int
0 else Int
1
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
IO (Vector (SymExpr sym ('BaseBVType 64)))
-> OverrideSim
p sym ext r args ret (Vector (SymExpr sym ('BaseBVType 64)))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Vector (SymExpr sym ('BaseBVType 64)))
-> OverrideSim
p sym ext r args ret (Vector (SymExpr sym ('BaseBVType 64))))
-> IO (Vector (SymExpr sym ('BaseBVType 64)))
-> OverrideSim
p sym ext r args ret (Vector (SymExpr sym ('BaseBVType 64)))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> IO (Vector (SymExpr sym ('BaseBVType 64)))
doPcmul sym
sym (Vector (SymExpr sym ('BaseBVType 64))
RegValue sym (VectorType (BVType 64))
xs Vector (SymExpr sym ('BaseBVType 64))
-> Int -> SymExpr sym ('BaseBVType 64)
forall a. Vector a -> Int -> a
V.! Int
xidx) (Vector (SymExpr sym ('BaseBVType 64))
RegValue sym (VectorType (BVType 64))
ys Vector (SymExpr sym ('BaseBVType 64))
-> Int -> SymExpr sym ('BaseBVType 64)
forall a. Vector a -> Int -> a
V.! Int
yidx)
Maybe Integer
_ ->
IO (Vector (SymExpr sym ('BaseBVType 64)))
-> OverrideSim
p sym ext r args ret (Vector (SymExpr sym ('BaseBVType 64)))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (Vector (SymExpr sym ('BaseBVType 64)))
-> OverrideSim
p sym ext r args ret (Vector (SymExpr sym ('BaseBVType 64))))
-> IO (Vector (SymExpr sym ('BaseBVType 64)))
-> OverrideSim
p sym ext r args ret (Vector (SymExpr sym ('BaseBVType 64)))
forall a b. (a -> b) -> a -> b
$ bak -> SimErrorReason -> IO (Vector (SymExpr sym ('BaseBVType 64)))
forall sym bak a.
IsSymBackend sym bak =>
bak -> SimErrorReason -> IO a
addFailedAssertion bak
bak (SimErrorReason -> IO (Vector (SymExpr sym ('BaseBVType 64))))
-> SimErrorReason -> IO (Vector (SymExpr sym ('BaseBVType 64)))
forall a b. (a -> b) -> a -> b
$ String -> String -> SimErrorReason
AssertFailureSimError
(String
"Illegal selector argument to llvm.x86.pclmulqdq")
([String] -> String
unwords [String
"Expected concrete value but got", Doc Any -> String
forall a. Show a => a -> String
show (SymExpr sym (BaseBVType 8) -> Doc Any
forall (tp :: BaseType) ann. SymExpr sym tp -> Doc ann
forall (e :: BaseType -> Type) (tp :: BaseType) ann.
IsExpr e =>
e tp -> Doc ann
printSymExpr RegValue sym (BVType 8)
SymExpr sym (BaseBVType 8)
imm)])
where
doPcmul :: sym -> SymBV sym 64 -> SymBV sym 64 -> IO (V.Vector (SymBV sym 64))
doPcmul :: sym
-> SymExpr sym ('BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> IO (Vector (SymExpr sym ('BaseBVType 64)))
doPcmul sym
sym SymExpr sym ('BaseBVType 64)
x SymExpr sym ('BaseBVType 64)
y =
do SymExpr sym (BaseBVType (64 + 64))
r <- sym
-> SymExpr sym ('BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> IO (SymExpr sym (BaseBVType (64 + 64)))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym (w + w))
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym (w + w))
carrylessMultiply sym
sym SymExpr sym ('BaseBVType 64)
x SymExpr sym ('BaseBVType 64)
y
SymExpr sym ('BaseBVType 64)
lo <- sym
-> NatRepr 64 -> SymBV sym 128 -> IO (SymExpr sym ('BaseBVType 64))
forall (r :: Natural) (w :: Natural).
(1 <= r, (r + 1) <= w) =>
sym -> NatRepr r -> SymBV sym w -> IO (SymBV sym r)
forall sym (r :: Natural) (w :: Natural).
(IsExprBuilder sym, 1 <= r, (r + 1) <= w) =>
sym -> NatRepr r -> SymBV sym w -> IO (SymBV sym r)
bvTrunc sym
sym (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @64) SymBV sym 128
SymExpr sym (BaseBVType (64 + 64))
r
SymExpr sym ('BaseBVType 64)
hi <- sym
-> NatRepr 64
-> NatRepr 64
-> SymBV sym 128
-> IO (SymExpr sym ('BaseBVType 64))
forall (idx :: Natural) (n :: Natural) (w :: Natural).
(1 <= n, (idx + n) <= w) =>
sym -> NatRepr idx -> NatRepr n -> SymBV sym w -> IO (SymBV sym n)
forall sym (idx :: Natural) (n :: Natural) (w :: Natural).
(IsExprBuilder sym, 1 <= n, (idx + n) <= w) =>
sym -> NatRepr idx -> NatRepr n -> SymBV sym w -> IO (SymBV sym n)
bvSelect sym
sym (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @64) (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @64) SymBV sym 128
SymExpr sym (BaseBVType (64 + 64))
r
Vector (SymExpr sym ('BaseBVType 64))
-> IO (Vector (SymExpr sym ('BaseBVType 64)))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Vector (SymExpr sym ('BaseBVType 64))
-> IO (Vector (SymExpr sym ('BaseBVType 64))))
-> Vector (SymExpr sym ('BaseBVType 64))
-> IO (Vector (SymExpr sym ('BaseBVType 64)))
forall a b. (a -> b) -> a -> b
$ [SymExpr sym ('BaseBVType 64)]
-> Vector (SymExpr sym ('BaseBVType 64))
forall a. [a] -> Vector a
V.fromList [ SymExpr sym ('BaseBVType 64)
lo, SymExpr sym ('BaseBVType 64)
hi ]
callStoreudq
:: ( IsSymInterface sym
, HasLLVMAnn sym
, HasPtrWidth wptr
, ?memOpts :: MemOptions )
=> GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (VectorType (BVType 8))
-> OverrideSim p sym ext r args ret ()
callStoreudq :: forall sym (wptr :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, HasLLVMAnn sym, HasPtrWidth wptr,
?memOpts::MemOptions) =>
GlobalVar Mem
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (VectorType (BVType 8))
-> OverrideSim p sym ext r args ret ()
callStoreudq GlobalVar Mem
mvar
(RegEntry sym (LLVMPointerType wptr)
-> RegValue sym (LLVMPointerType wptr)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (LLVMPointerType wptr)
dest)
(RegEntry sym (VectorType (BVType 8))
-> RegValue sym (VectorType (BVType 8))
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (VectorType (BVType 8))
vec) =
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret ())
-> OverrideSim p sym ext r args ret ()
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret ())
-> OverrideSim p sym ext r args ret ())
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret ())
-> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$ \bak
bak -> do
MemImpl sym
mem <- GlobalVar Mem
-> OverrideSim p sym ext r args ret (RegValue sym Mem)
forall sym (tp :: CrucibleType) p ext rtp
(args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
GlobalVar tp
-> OverrideSim p sym ext rtp args ret (RegValue sym tp)
readGlobal GlobalVar Mem
mvar
Bool
-> OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ()
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless (Vector (SymExpr sym (BaseBVType 8)) -> Int
forall a. Vector a -> Int
V.length Vector (SymExpr sym (BaseBVType 8))
RegValue sym (VectorType (BVType 8))
vec Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
16) (OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ())
-> OverrideSim p sym ext r args ret ()
-> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$
IO () -> OverrideSim p sym ext r args ret ()
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> OverrideSim p sym ext r args ret ())
-> IO () -> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$ bak -> SimErrorReason -> IO ()
forall sym bak a.
IsSymBackend sym bak =>
bak -> SimErrorReason -> IO a
addFailedAssertion bak
bak (SimErrorReason -> IO ()) -> SimErrorReason -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> String -> SimErrorReason
AssertFailureSimError
(String
"Vector length mismatch in stored_qu intrinsic.")
([String] -> String
unwords [String
"Expected <16 x i8>, but got vector of length", Int -> String
forall a. Show a => a -> String
show (Vector (SymExpr sym (BaseBVType 8)) -> Int
forall a. Vector a -> Int
V.length Vector (SymExpr sym (BaseBVType 8))
RegValue sym (VectorType (BVType 8))
vec)])
MemImpl sym
mem' <- IO (MemImpl sym) -> OverrideSim p sym ext r args ret (MemImpl sym)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (MemImpl sym)
-> OverrideSim p sym ext r args ret (MemImpl sym))
-> IO (MemImpl sym)
-> OverrideSim p sym ext r args ret (MemImpl sym)
forall a b. (a -> b) -> a -> b
$ bak
-> MemImpl sym
-> RegValue sym (LLVMPointerType wptr)
-> TypeRepr (VectorType (BVType 8))
-> StorageType
-> Alignment
-> RegValue sym (VectorType (BVType 8))
-> IO (MemImpl sym)
forall sym bak (wptr :: Natural) (tp :: CrucibleType).
(IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym,
?memOpts::MemOptions) =>
bak
-> MemImpl sym
-> LLVMPtr sym wptr
-> TypeRepr tp
-> StorageType
-> Alignment
-> RegValue sym tp
-> IO (MemImpl sym)
doStore
bak
bak
MemImpl sym
mem
RegValue sym (LLVMPointerType wptr)
dest
(TypeRepr (BVType 8) -> TypeRepr (VectorType (BVType 8))
forall (tp1 :: CrucibleType).
TypeRepr tp1 -> TypeRepr ('VectorType tp1)
VectorRepr (forall (n :: Natural). (1 <= n, KnownNat n) => TypeRepr (BVType n)
KnownBV @8))
(Natural -> StorageType -> StorageType
arrayType Natural
16 (Bytes -> StorageType
bitvectorType (Integer -> Bytes
Bytes Integer
1)))
Alignment
noAlignment
RegValue sym (VectorType (BVType 8))
vec
GlobalVar Mem
-> RegValue sym Mem -> OverrideSim p sym ext r args ret ()
forall (tp :: CrucibleType) sym p ext rtp
(args :: Ctx CrucibleType) (ret :: CrucibleType).
GlobalVar tp
-> RegValue sym tp -> OverrideSim p sym ext rtp args ret ()
writeGlobal GlobalVar Mem
mvar RegValue sym Mem
MemImpl sym
mem'
callObjectsize
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize :: forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize GlobalVar Mem
_mvar NatRepr w
w
(RegEntry sym (LLVMPointerType wptr)
-> RegValue sym (LLVMPointerType wptr)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (LLVMPointerType wptr)
_ptr)
(RegEntry sym (BVType 1) -> RegValue sym (BVType 1)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType 1)
flag) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
t <- sym -> SymBV sym 1 -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (Pred sym)
bvIsNonzero sym
sym RegValue sym (BVType 1)
SymBV sym 1
flag
SymExpr sym ('BaseBVType w)
z <- sym -> NatRepr w -> IO (SymExpr sym ('BaseBVType w))
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvZero sym
sym NatRepr w
w
SymExpr sym ('BaseBVType w)
n <- sym
-> SymExpr sym ('BaseBVType w) -> IO (SymExpr sym ('BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
bvNotBits sym
sym SymExpr sym ('BaseBVType w)
z
sym
-> SymExpr sym BaseBoolType
-> SymExpr sym ('BaseBVType w)
-> SymExpr sym ('BaseBVType w)
-> IO (SymExpr sym ('BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
t SymExpr sym ('BaseBVType w)
z SymExpr sym ('BaseBVType w)
n
callObjectsize_null
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null :: forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null GlobalVar Mem
mvar NatRepr w
w RegEntry sym (LLVMPointerType wptr)
ptr RegEntry sym (BVType 1)
flag RegEntry sym (BVType 1)
_nullUnknown = GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize GlobalVar Mem
mvar NatRepr w
w RegEntry sym (LLVMPointerType wptr)
ptr RegEntry sym (BVType 1)
flag
callObjectsize_null_dynamic
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null_dynamic :: forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize_null_dynamic GlobalVar Mem
mvar NatRepr w
w RegEntry sym (LLVMPointerType wptr)
ptr RegEntry sym (BVType 1)
flag RegEntry sym (BVType 1)
_nullUnknown (RegEntry sym (BVType 1) -> RegValue sym (BVType 1)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType 1)
dynamic) =
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> do
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
IO () -> OverrideSim p sym ext r args ret ()
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO () -> OverrideSim p sym ext r args ret ())
-> IO () -> OverrideSim p sym ext r args ret ()
forall a b. (a -> b) -> a -> b
$
do SymExpr sym BaseBoolType
notDynamic <- sym -> SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType)
forall sym. IsExprBuilder sym => sym -> Pred sym -> IO (Pred sym)
notPred sym
sym (SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType))
-> IO (SymExpr sym BaseBoolType) -> IO (SymExpr sym BaseBoolType)
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SymBV sym 1 -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (Pred sym)
bvIsNonzero sym
sym RegValue sym (BVType 1)
SymBV sym 1
dynamic
bak -> SymExpr sym BaseBoolType -> SimErrorReason -> IO ()
forall sym bak.
IsSymBackend sym bak =>
bak -> Pred sym -> SimErrorReason -> IO ()
assert bak
bak SymExpr sym BaseBoolType
notDynamic (String -> String -> SimErrorReason
AssertFailureSimError String
"llvm.objectsize called with `dynamic` set to `true`" String
"")
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callObjectsize GlobalVar Mem
mvar NatRepr w
w RegEntry sym (LLVMPointerType wptr)
ptr RegEntry sym (BVType 1)
flag
callCtlz
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCtlz :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCtlz GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
val)
(RegEntry sym (BVType 1) -> RegValue sym (BVType 1)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType 1)
isZeroUndef) =
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
isNonzero <- sym -> SymExpr sym ('BaseBVType w) -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (Pred sym)
bvIsNonzero sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
val
SymExpr sym BaseBoolType
zeroOK <- sym -> SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType)
forall sym. IsExprBuilder sym => sym -> Pred sym -> IO (Pred sym)
notPred sym
sym (SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType))
-> IO (SymExpr sym BaseBoolType) -> IO (SymExpr sym BaseBoolType)
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SymBV sym 1 -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (Pred sym)
bvIsNonzero sym
sym RegValue sym (BVType 1)
SymBV sym 1
isZeroUndef
SymExpr sym BaseBoolType
p <- sym
-> SymExpr sym BaseBoolType
-> SymExpr sym BaseBoolType
-> IO (SymExpr sym BaseBoolType)
forall sym.
IsExprBuilder sym =>
sym -> Pred sym -> Pred sym -> IO (Pred sym)
orPred sym
sym SymExpr sym BaseBoolType
isNonzero SymExpr sym BaseBoolType
zeroOK
bak -> SymExpr sym BaseBoolType -> SimErrorReason -> IO ()
forall sym bak.
IsSymBackend sym bak =>
bak -> Pred sym -> SimErrorReason -> IO ()
assert bak
bak SymExpr sym BaseBoolType
p (String -> String -> SimErrorReason
AssertFailureSimError String
"Ctlz called with disallowed zero value" String
"")
sym
-> SymExpr sym ('BaseBVType w) -> IO (SymExpr sym ('BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
bvCountLeadingZeros sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
val
callFshl
:: (1 <= w, IsSymInterface sym)
=> NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callFshl :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callFshl NatRepr w
w RegEntry sym (BVType w)
x RegEntry sym (BVType w)
y RegEntry sym (BVType w)
amt =
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ do
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
LeqProof 1 (w + w)
LeqProof <- LeqProof 1 (w + w) -> IO (LeqProof 1 (w + w))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (LeqProof 1 w -> LeqProof 1 (w + w)
forall (n :: Natural). LeqProof 1 n -> LeqProof 1 (n + n)
dblPosIsPos (NatRepr 1 -> NatRepr w -> LeqProof 1 w
forall (m :: Natural) (n :: Natural) (f :: Natural -> Type)
(g :: Natural -> Type).
(m <= n) =>
f m -> g n -> LeqProof m n
leqProof (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1) NatRepr w
w))
Just LeqProof (w + 1) (w + w)
LeqProof <- Maybe (LeqProof (w + 1) (w + w))
-> IO (Maybe (LeqProof (w + 1) (w + w)))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (NatRepr (w + 1)
-> NatRepr (w + w) -> Maybe (LeqProof (w + 1) (w + w))
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> Maybe (LeqProof m n)
testLeq (NatRepr w -> NatRepr 1 -> NatRepr (w + 1)
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)) (NatRepr w -> NatRepr w -> NatRepr (w + w)
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w NatRepr w
w))
SymExpr sym (BaseBVType (w + w))
xy <- sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym (BaseBVType (w + w)))
forall (u :: Natural) (v :: Natural).
(1 <= u, 1 <= v) =>
sym -> SymBV sym u -> SymBV sym v -> IO (SymBV sym (u + v))
forall sym (u :: Natural) (v :: Natural).
(IsExprBuilder sym, 1 <= u, 1 <= v) =>
sym -> SymBV sym u -> SymBV sym v -> IO (SymBV sym (u + v))
bvConcat sym
sym (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType w)
x) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType w)
y)
SymBV sym w
m <- sym -> NatRepr w -> BV w -> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
bvLit sym
sym NatRepr w
w (NatRepr w -> BV w
forall (w :: Natural). NatRepr w -> BV w
BV.width NatRepr w
w)
SymBV sym w
mamt <- sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUrem sym
sym (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType w)
amt) SymBV sym w
m
SymExpr sym (BaseBVType (w + w))
mamt' <- sym
-> NatRepr (w + w)
-> SymBV sym w
-> IO (SymExpr sym (BaseBVType (w + w)))
forall (u :: Natural) (r :: Natural).
(1 <= u, (u + 1) <= r) =>
sym -> NatRepr r -> SymBV sym u -> IO (SymBV sym r)
forall sym (u :: Natural) (r :: Natural).
(IsExprBuilder sym, 1 <= u, (u + 1) <= r) =>
sym -> NatRepr r -> SymBV sym u -> IO (SymBV sym r)
bvZext sym
sym (NatRepr w -> NatRepr w -> NatRepr (w + w)
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w NatRepr w
w) SymBV sym w
mamt
SymExpr sym (BaseBVType (w + w))
z <- sym
-> SymExpr sym (BaseBVType (w + w))
-> SymExpr sym (BaseBVType (w + w))
-> IO (SymExpr sym (BaseBVType (w + w)))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvShl sym
sym SymExpr sym (BaseBVType (w + w))
xy SymExpr sym (BaseBVType (w + w))
mamt'
sym
-> NatRepr w
-> NatRepr w
-> SymExpr sym (BaseBVType (w + w))
-> IO (SymBV sym w)
forall (idx :: Natural) (n :: Natural) (w :: Natural).
(1 <= n, (idx + n) <= w) =>
sym -> NatRepr idx -> NatRepr n -> SymBV sym w -> IO (SymBV sym n)
forall sym (idx :: Natural) (n :: Natural) (w :: Natural).
(IsExprBuilder sym, 1 <= n, (idx + n) <= w) =>
sym -> NatRepr idx -> NatRepr n -> SymBV sym w -> IO (SymBV sym n)
bvSelect sym
sym NatRepr w
w NatRepr w
w SymExpr sym (BaseBVType (w + w))
z
callFshr
:: (1 <= w, IsSymInterface sym)
=> NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callFshr :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
NatRepr w
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callFshr NatRepr w
w RegEntry sym (BVType w)
x RegEntry sym (BVType w)
y RegEntry sym (BVType w)
amt =
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ do
LeqProof 1 (w + w)
LeqProof <- LeqProof 1 (w + w) -> IO (LeqProof 1 (w + w))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (LeqProof 1 w -> LeqProof 1 (w + w)
forall (n :: Natural). LeqProof 1 n -> LeqProof 1 (n + n)
dblPosIsPos (NatRepr 1 -> NatRepr w -> LeqProof 1 w
forall (m :: Natural) (n :: Natural) (f :: Natural -> Type)
(g :: Natural -> Type).
(m <= n) =>
f m -> g n -> LeqProof m n
leqProof (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1) NatRepr w
w))
LeqProof w (w + w)
LeqProof <- LeqProof w (w + w) -> IO (LeqProof w (w + w))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (NatRepr w -> NatRepr w -> LeqProof w (w + w)
forall (f :: Natural -> Type) (m :: Natural) (g :: Natural -> Type)
(n :: Natural).
f m -> g n -> LeqProof n (m + n)
addPrefixIsLeq NatRepr w
w NatRepr w
w)
Just LeqProof (w + 1) (w + w)
LeqProof <- Maybe (LeqProof (w + 1) (w + w))
-> IO (Maybe (LeqProof (w + 1) (w + w)))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (NatRepr (w + 1)
-> NatRepr (w + w) -> Maybe (LeqProof (w + 1) (w + w))
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> Maybe (LeqProof m n)
testLeq (NatRepr w -> NatRepr 1 -> NatRepr (w + 1)
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)) (NatRepr w -> NatRepr w -> NatRepr (w + w)
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w NatRepr w
w))
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
SymExpr sym (BaseBVType (w + w))
xy <- sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym (BaseBVType (w + w)))
forall (u :: Natural) (v :: Natural).
(1 <= u, 1 <= v) =>
sym -> SymBV sym u -> SymBV sym v -> IO (SymBV sym (u + v))
forall sym (u :: Natural) (v :: Natural).
(IsExprBuilder sym, 1 <= u, 1 <= v) =>
sym -> SymBV sym u -> SymBV sym v -> IO (SymBV sym (u + v))
bvConcat sym
sym (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType w)
x) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType w)
y)
SymBV sym w
m <- sym -> NatRepr w -> BV w -> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
bvLit sym
sym NatRepr w
w (NatRepr w -> BV w
forall (w :: Natural). NatRepr w -> BV w
BV.width NatRepr w
w)
SymBV sym w
mamt <- sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUrem sym
sym (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue RegEntry sym (BVType w)
amt) SymBV sym w
m
SymExpr sym (BaseBVType (w + w))
mamt' <- sym
-> NatRepr (w + w)
-> SymBV sym w
-> IO (SymExpr sym (BaseBVType (w + w)))
forall (u :: Natural) (r :: Natural).
(1 <= u, (u + 1) <= r) =>
sym -> NatRepr r -> SymBV sym u -> IO (SymBV sym r)
forall sym (u :: Natural) (r :: Natural).
(IsExprBuilder sym, 1 <= u, (u + 1) <= r) =>
sym -> NatRepr r -> SymBV sym u -> IO (SymBV sym r)
bvZext sym
sym (NatRepr w -> NatRepr w -> NatRepr (w + w)
forall (m :: Natural) (n :: Natural).
NatRepr m -> NatRepr n -> NatRepr (m + n)
addNat NatRepr w
w NatRepr w
w) SymBV sym w
mamt
SymExpr sym (BaseBVType (w + w))
z <- sym
-> SymExpr sym (BaseBVType (w + w))
-> SymExpr sym (BaseBVType (w + w))
-> IO (SymExpr sym (BaseBVType (w + w)))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvLshr sym
sym SymExpr sym (BaseBVType (w + w))
xy SymExpr sym (BaseBVType (w + w))
mamt'
sym
-> NatRepr 0
-> NatRepr w
-> SymExpr sym (BaseBVType (w + w))
-> IO (SymBV sym w)
forall (idx :: Natural) (n :: Natural) (w :: Natural).
(1 <= n, (idx + n) <= w) =>
sym -> NatRepr idx -> NatRepr n -> SymBV sym w -> IO (SymBV sym n)
forall sym (idx :: Natural) (n :: Natural) (w :: Natural).
(IsExprBuilder sym, 1 <= n, (idx + n) <= w) =>
sym -> NatRepr idx -> NatRepr n -> SymBV sym w -> IO (SymBV sym n)
bvSelect sym
sym (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @0) NatRepr w
w SymExpr sym (BaseBVType (w + w))
z
callSaddWithOverflow
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (StructType (EmptyCtx ::> BVType w ::> BVType 1)))
callSaddWithOverflow :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callSaddWithOverflow GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x)
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) =
(forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> (forall bak.
IsSymBackend sym bak =>
bak
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> IO
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1))))
-> IO
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
forall a b. (a -> b) -> a -> b
$ do
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
(SymExpr sym BaseBoolType
ov, SymExpr sym (BaseBVType w)
z) <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym BaseBoolType, SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym BaseBoolType, SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym, SymBV sym w)
addSignedOF sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
y
SymExpr sym (BaseBVType 1)
ov' <- sym
-> SymExpr sym BaseBoolType
-> NatRepr 1
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymExpr sym BaseBoolType -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> NatRepr w -> IO (SymBV sym w)
predToBV sym
sym SymExpr sym BaseBoolType
ov (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)
Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
-> IO
(Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) ::> BVType 1))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Assignment (RegValue' sym) EmptyCtx
forall {k} (ctx :: Ctx k) (f :: k -> Type).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (RegValue' sym) EmptyCtx
-> RegValue' sym (BVType w)
-> Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType w) -> RegValue' sym (BVType w)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
z Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
-> RegValue' sym (BVType 1)
-> Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) ::> BVType 1)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType 1) -> RegValue' sym (BVType 1)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType 1)
SymExpr sym (BaseBVType 1)
ov')
callUaddWithOverflow
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (StructType (EmptyCtx ::> BVType w ::> BVType 1)))
callUaddWithOverflow :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callUaddWithOverflow GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x)
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)))
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a b. (a -> b) -> a -> b
$ do
(SymExpr sym BaseBoolType
ov, SymExpr sym (BaseBVType w)
z) <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym BaseBoolType, SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym BaseBoolType, SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym, SymBV sym w)
addUnsignedOF sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
y
SymExpr sym (BaseBVType 1)
ov' <- sym
-> SymExpr sym BaseBoolType
-> NatRepr 1
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymExpr sym BaseBoolType -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> NatRepr w -> IO (SymBV sym w)
predToBV sym
sym SymExpr sym BaseBoolType
ov (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)
Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Assignment (RegValue' sym) EmptyCtx
forall {k} (ctx :: Ctx k) (f :: k -> Type).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (RegValue' sym) EmptyCtx
-> RegValue' sym (BVType w)
-> Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType w) -> RegValue' sym (BVType w)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
z Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
-> RegValue' sym (BVType 1)
-> Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType 1) -> RegValue' sym (BVType 1)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType 1)
SymExpr sym (BaseBVType 1)
ov')
callUsubWithOverflow
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (StructType (EmptyCtx ::> BVType w ::> BVType 1)))
callUsubWithOverflow :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callUsubWithOverflow GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x)
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)))
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a b. (a -> b) -> a -> b
$ do
(SymExpr sym BaseBoolType
ov, SymExpr sym (BaseBVType w)
z) <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym BaseBoolType, SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym BaseBoolType, SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym, SymBV sym w)
subUnsignedOF sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
y
SymExpr sym (BaseBVType 1)
ov' <- sym
-> SymExpr sym BaseBoolType
-> NatRepr 1
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymExpr sym BaseBoolType -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> NatRepr w -> IO (SymBV sym w)
predToBV sym
sym SymExpr sym BaseBoolType
ov (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)
Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Assignment (RegValue' sym) EmptyCtx
forall {k} (ctx :: Ctx k) (f :: k -> Type).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (RegValue' sym) EmptyCtx
-> RegValue' sym (BVType w)
-> Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType w) -> RegValue' sym (BVType w)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
z Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
-> RegValue' sym (BVType 1)
-> Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType 1) -> RegValue' sym (BVType 1)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType 1)
SymExpr sym (BaseBVType 1)
ov')
callSsubWithOverflow
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (StructType (EmptyCtx ::> BVType w ::> BVType 1)))
callSsubWithOverflow :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callSsubWithOverflow GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x)
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)))
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a b. (a -> b) -> a -> b
$ do
(SymExpr sym BaseBoolType
ov, SymExpr sym (BaseBVType w)
z) <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym BaseBoolType, SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym BaseBoolType, SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym, SymBV sym w)
subSignedOF sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
y
SymExpr sym (BaseBVType 1)
ov' <- sym
-> SymExpr sym BaseBoolType
-> NatRepr 1
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymExpr sym BaseBoolType -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> NatRepr w -> IO (SymBV sym w)
predToBV sym
sym SymExpr sym BaseBoolType
ov (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)
Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Assignment (RegValue' sym) EmptyCtx
forall {k} (ctx :: Ctx k) (f :: k -> Type).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (RegValue' sym) EmptyCtx
-> RegValue' sym (BVType w)
-> Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType w) -> RegValue' sym (BVType w)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
z Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
-> RegValue' sym (BVType 1)
-> Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType 1) -> RegValue' sym (BVType 1)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType 1)
SymExpr sym (BaseBVType 1)
ov')
callSmulWithOverflow
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (StructType (EmptyCtx ::> BVType w ::> BVType 1)))
callSmulWithOverflow :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callSmulWithOverflow GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x)
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)))
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a b. (a -> b) -> a -> b
$ do
(SymExpr sym BaseBoolType
ov, SymExpr sym (BaseBVType w)
z) <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym BaseBoolType, SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym BaseBoolType, SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym, SymBV sym w)
mulSignedOF sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
y
SymExpr sym (BaseBVType 1)
ov' <- sym
-> SymExpr sym BaseBoolType
-> NatRepr 1
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymExpr sym BaseBoolType -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> NatRepr w -> IO (SymBV sym w)
predToBV sym
sym SymExpr sym BaseBoolType
ov (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)
Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Assignment (RegValue' sym) EmptyCtx
forall {k} (ctx :: Ctx k) (f :: k -> Type).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (RegValue' sym) EmptyCtx
-> RegValue' sym (BVType w)
-> Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType w) -> RegValue' sym (BVType w)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
z Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
-> RegValue' sym (BVType 1)
-> Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType 1) -> RegValue' sym (BVType 1)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType 1)
SymExpr sym (BaseBVType 1)
ov')
callUmulWithOverflow
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (StructType (EmptyCtx ::> BVType w ::> BVType 1)))
callUmulWithOverflow :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim
p
sym
ext
r
args
ret
(RegValue sym (StructType ((EmptyCtx ::> BVType w) ::> BVType 1)))
callUmulWithOverflow GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x)
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)))
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a b. (a -> b) -> a -> b
$ do
(SymExpr sym BaseBoolType
ov, SymExpr sym (BaseBVType w)
z) <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym BaseBoolType, SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymExpr sym BaseBoolType, SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym, SymBV sym w)
mulUnsignedOF sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
y
SymExpr sym (BaseBVType 1)
ov' <- sym
-> SymExpr sym BaseBoolType
-> NatRepr 1
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymExpr sym BaseBoolType -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> NatRepr w -> IO (SymBV sym w)
predToBV sym
sym SymExpr sym BaseBoolType
ov (forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1)
Assignment (RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
-> IO
(Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1))
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (Assignment (RegValue' sym) EmptyCtx
forall {k} (ctx :: Ctx k) (f :: k -> Type).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (RegValue' sym) EmptyCtx
-> RegValue' sym (BVType w)
-> Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType w) -> RegValue' sym (BVType w)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
z Assignment (RegValue' sym) (EmptyCtx ::> BVType w)
-> RegValue' sym (BVType 1)
-> Assignment
(RegValue' sym) ((EmptyCtx ::> BVType w) '::> BVType 1)
forall {k} (ctx' :: Ctx k) (f :: k -> Type) (ctx :: Ctx k)
(tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> RegValue sym (BVType 1) -> RegValue' sym (BVType 1)
forall sym (tp :: CrucibleType).
RegValue sym tp -> RegValue' sym tp
RV RegValue sym (BVType 1)
SymExpr sym (BaseBVType 1)
ov')
callUmax
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callUmax :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callUmax GlobalVar Mem
_mvar (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType w)
-> SymExpr sym ('BaseBVType w)
-> IO (SymExpr sym ('BaseBVType w))
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUmax sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
y
bvUmax ::
(IsExprBuilder sym, 1 <= w)
=> sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
bvUmax :: forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUmax sym
sym SymBV sym w
x SymBV sym w
y = do
SymExpr sym BaseBoolType
xGtY <- sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym)
bvUgt sym
sym SymBV sym w
x SymBV sym w
y
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
xGtY SymBV sym w
x SymBV sym w
y
callUmin
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callUmin :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callUmin GlobalVar Mem
_mvar (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType w)
-> SymExpr sym ('BaseBVType w)
-> IO (SymExpr sym ('BaseBVType w))
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUmin sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
y
bvUmin ::
(IsExprBuilder sym, 1 <= w)
=> sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
bvUmin :: forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUmin sym
sym SymBV sym w
x SymBV sym w
y = do
SymExpr sym BaseBoolType
xLtY <- sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym)
bvUlt sym
sym SymBV sym w
x SymBV sym w
y
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
xLtY SymBV sym w
x SymBV sym w
y
callSmax
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callSmax :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callSmax GlobalVar Mem
_mvar (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType w)
-> SymExpr sym ('BaseBVType w)
-> IO (SymExpr sym ('BaseBVType w))
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvSmax sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
y
bvSmax ::
(IsExprBuilder sym, 1 <= w)
=> sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
bvSmax :: forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvSmax sym
sym SymBV sym w
x SymBV sym w
y = do
SymExpr sym BaseBoolType
xGtY <- sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym)
bvSgt sym
sym SymBV sym w
x SymBV sym w
y
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
xGtY SymBV sym w
x SymBV sym w
y
callSmin
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callSmin :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callSmin GlobalVar Mem
_mvar (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
x) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType w)
-> SymExpr sym ('BaseBVType w)
-> IO (SymExpr sym ('BaseBVType w))
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvSmin sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
x RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
y
bvSmin ::
(IsExprBuilder sym, 1 <= w)
=> sym
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
bvSmin :: forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvSmin sym
sym SymBV sym w
x SymBV sym w
y = do
SymExpr sym BaseBoolType
xLtY <- sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (Pred sym)
bvSlt sym
sym SymBV sym w
x SymBV sym w
y
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
xLtY SymBV sym w
x SymBV sym w
y
callCttz
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCttz :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> RegEntry sym (BVType 1)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCttz GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
val)
(RegEntry sym (BVType 1) -> RegValue sym (BVType 1)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType 1)
isZeroUndef) =
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ \bak
bak -> do
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w)))
-> IO (RegValue sym (BVType w))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
isNonzero <- sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (Pred sym)
bvIsNonzero sym
sym RegValue sym (BVType w)
SymBV sym w
val
SymExpr sym BaseBoolType
zeroOK <- sym -> SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType)
forall sym. IsExprBuilder sym => sym -> Pred sym -> IO (Pred sym)
notPred sym
sym (SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType))
-> IO (SymExpr sym BaseBoolType) -> IO (SymExpr sym BaseBoolType)
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SymBV sym 1 -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (Pred sym)
bvIsNonzero sym
sym RegValue sym (BVType 1)
SymBV sym 1
isZeroUndef
SymExpr sym BaseBoolType
p <- sym
-> SymExpr sym BaseBoolType
-> SymExpr sym BaseBoolType
-> IO (SymExpr sym BaseBoolType)
forall sym.
IsExprBuilder sym =>
sym -> Pred sym -> Pred sym -> IO (Pred sym)
orPred sym
sym SymExpr sym BaseBoolType
isNonzero SymExpr sym BaseBoolType
zeroOK
bak -> SymExpr sym BaseBoolType -> SimErrorReason -> IO ()
forall sym bak.
IsSymBackend sym bak =>
bak -> Pred sym -> SimErrorReason -> IO ()
assert bak
bak SymExpr sym BaseBoolType
p (String -> String -> SimErrorReason
AssertFailureSimError String
"Cttz called with disallowed zero value" String
"")
sym -> SymBV sym w -> IO (SymBV sym w)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
bvCountTrailingZeros sym
sym RegValue sym (BVType w)
SymBV sym w
val
callCtpop
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCtpop :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callCtpop GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
val) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType w) -> IO (SymExpr sym ('BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
bvPopcount sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
val
callBitreverse
:: (1 <= w, IsSymInterface sym)
=> GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callBitreverse :: forall (w :: Natural) sym p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(1 <= w, IsSymInterface sym) =>
GlobalVar Mem
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
callBitreverse GlobalVar Mem
_mvar
(RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
val) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w)))
-> IO (SymExpr sym ('BaseBVType w))
-> OverrideSim p sym ext r args ret (SymExpr sym ('BaseBVType w))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym ('BaseBVType w) -> IO (SymExpr sym ('BaseBVType w))
forall sym (w :: Natural).
(1 <= w, IsExprBuilder sym) =>
sym -> SymBV sym w -> IO (SymBV sym w)
bvBitreverse sym
sym RegValue sym (BVType w)
SymExpr sym ('BaseBVType w)
val
callCopysign ::
forall fi p sym ext r args ret.
IsSymInterface sym =>
RegEntry sym (FloatType fi) ->
RegEntry sym (FloatType fi) ->
OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
callCopysign :: forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (FloatType fi))
callCopysign
(RegEntry sym (FloatType fi) -> RegValue sym (FloatType fi)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (FloatType fi)
x)
(RegEntry sym (FloatType fi) -> RegValue sym (FloatType fi)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (FloatType fi)
y) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
IO (SymExpr sym (SymInterpretedFloatType sym fi))
-> OverrideSim
p sym ext r args ret (SymExpr sym (SymInterpretedFloatType sym fi))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (SymInterpretedFloatType sym fi))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (SymInterpretedFloatType sym fi)))
-> IO (SymExpr sym (SymInterpretedFloatType sym fi))
-> OverrideSim
p sym ext r args ret (SymExpr sym (SymInterpretedFloatType sym fi))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
xIsNeg <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsNeg @_ @fi sym
sym RegValue sym (FloatType fi)
SymExpr sym (SymInterpretedFloatType sym fi)
x
SymExpr sym BaseBoolType
yIsNeg <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsNeg @_ @fi sym
sym RegValue sym (FloatType fi)
SymExpr sym (SymInterpretedFloatType sym fi)
y
SymExpr sym BaseBoolType
signsSame <- sym
-> SymExpr sym BaseBoolType
-> SymExpr sym BaseBoolType
-> IO (SymExpr sym BaseBoolType)
forall sym.
IsExprBuilder sym =>
sym -> Pred sym -> Pred sym -> IO (Pred sym)
eqPred sym
sym SymExpr sym BaseBoolType
xIsNeg SymExpr sym BaseBoolType
yIsNeg
SymExpr sym (SymInterpretedFloatType sym fi)
xNegated <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym
-> SymInterpretedFloat sym fi -> IO (SymInterpretedFloat sym fi)
iFloatNeg @_ @fi sym
sym RegValue sym (FloatType fi)
SymExpr sym (SymInterpretedFloatType sym fi)
x
forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym
-> Pred sym
-> SymInterpretedFloat sym fi
-> SymInterpretedFloat sym fi
-> IO (SymInterpretedFloat sym fi)
iFloatIte @_ @fi sym
sym SymExpr sym BaseBoolType
signsSame RegValue sym (FloatType fi)
SymExpr sym (SymInterpretedFloatType sym fi)
x SymExpr sym (SymInterpretedFloatType sym fi)
xNegated
callIsFpclass ::
forall fi p sym ext r args ret.
IsSymInterface sym =>
RegEntry sym (FloatType fi) ->
RegEntry sym (BVType 32) ->
OverrideSim p sym ext r args ret (RegValue sym (BVType 1))
callIsFpclass :: forall (fi :: FloatInfo) p sym ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
IsSymInterface sym =>
RegEntry sym (FloatType fi)
-> RegEntry sym (BVType 32)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType 1))
callIsFpclass regOp :: RegEntry sym (FloatType fi)
regOp@(RegEntry sym (FloatType fi) -> RegValue sym (FloatType fi)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (FloatType fi)
op) (RegEntry sym (BVType 32) -> RegValue sym (BVType 32)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType 32)
test) = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
let w1 :: NatRepr 1
w1 = forall (n :: Natural). KnownNat n => NatRepr n
knownNat @1
SymExpr sym (BaseBVType 1)
bv1 <- IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr 1 -> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvZero sym
sym NatRepr 1
w1
SymExpr sym (BaseBVType 1)
bv0 <- IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr 1 -> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvOne sym
sym NatRepr 1
w1
let negative :: SymExpr sym (BaseBVType 1) -> IO (SymExpr sym (BaseBVType 1))
negative SymExpr sym (BaseBVType 1)
bit = IO (SymExpr sym (BaseBVType 1)) -> IO (SymExpr sym (BaseBVType 1))
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
isNeg <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsNeg @_ @fi sym
sym RegValue sym (FloatType fi)
SymInterpretedFloat sym fi
op
IO (SymExpr sym (BaseBVType 1)) -> IO (SymExpr sym (BaseBVType 1))
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
isNeg SymExpr sym (BaseBVType 1)
bit SymExpr sym (BaseBVType 1)
bv0
let positive :: SymExpr sym (BaseBVType 1) -> IO (SymExpr sym (BaseBVType 1))
positive SymExpr sym (BaseBVType 1)
bit = IO (SymExpr sym (BaseBVType 1)) -> IO (SymExpr sym (BaseBVType 1))
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
isPos <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsPos @_ @fi sym
sym RegValue sym (FloatType fi)
SymInterpretedFloat sym fi
op
IO (SymExpr sym (BaseBVType 1)) -> IO (SymExpr sym (BaseBVType 1))
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
isPos SymExpr sym (BaseBVType 1)
bit SymExpr sym (BaseBVType 1)
bv0
let negAndPos :: IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
negAndPos IO (SymExpr sym (BaseBVType 1))
doCheck = IO (SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym (BaseBVType 1)
check <- IO (SymExpr sym (BaseBVType 1))
doCheck
SymExpr sym (BaseBVType 1)
checkN <- SymExpr sym (BaseBVType 1) -> IO (SymExpr sym (BaseBVType 1))
negative SymExpr sym (BaseBVType 1)
check
SymExpr sym (BaseBVType 1)
checkP <- SymExpr sym (BaseBVType 1) -> IO (SymExpr sym (BaseBVType 1))
positive SymExpr sym (BaseBVType 1)
check
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a. a -> IO a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (SymExpr sym (BaseBVType 1)
checkN, SymExpr sym (BaseBVType 1)
checkP)
let callIsInf :: SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsInf SymInterpretedFloat sym fi
x = do
SymExpr sym BaseBoolType
isInf <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsInf @_ @fi sym
sym SymInterpretedFloat sym fi
x
sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
isInf SymExpr sym (BaseBVType 1)
bv1 SymExpr sym (BaseBVType 1)
bv0
let callIsNormal :: SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsNormal SymInterpretedFloat sym fi
x = do
SymExpr sym BaseBoolType
isNorm <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsNorm @_ @fi sym
sym SymInterpretedFloat sym fi
x
sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
isNorm SymExpr sym (BaseBVType 1)
bv1 SymExpr sym (BaseBVType 1)
bv0
let callIsSubnormal :: SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsSubnormal SymInterpretedFloat sym fi
x = do
SymExpr sym BaseBoolType
isSubnorm <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsSubnorm @_ @fi sym
sym SymInterpretedFloat sym fi
x
sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
isSubnorm SymExpr sym (BaseBVType 1)
bv1 SymExpr sym (BaseBVType 1)
bv0
let callIsZero :: SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsZero SymInterpretedFloat sym fi
x = do
SymExpr sym BaseBoolType
is0 <- forall sym (fi :: FloatInfo).
IsInterpretedFloatExprBuilder sym =>
sym -> SymInterpretedFloat sym fi -> IO (Pred sym)
iFloatIsZero @_ @fi sym
sym SymInterpretedFloat sym fi
x
sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
is0 SymExpr sym (BaseBVType 1)
bv1 SymExpr sym (BaseBVType 1)
bv0
SymExpr sym (BaseBVType 1)
isNan <- NatRepr 1
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType 1))
forall (fi :: FloatInfo) (w :: Natural) p sym ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(IsSymInterface sym, 1 <= w) =>
NatRepr w
-> RegEntry sym (FloatType fi)
-> OverrideSim p sym ext r args ret (RegValue sym (BVType w))
Libc.callIsnan NatRepr 1
w1 RegEntry sym (FloatType fi)
regOp
(SymExpr sym (BaseBVType 1)
isInfN, SymExpr sym (BaseBVType 1)
isInfP) <- IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
negAndPos (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsInf RegValue sym (FloatType fi)
SymInterpretedFloat sym fi
op
(SymExpr sym (BaseBVType 1)
isNormN, SymExpr sym (BaseBVType 1)
isNormP) <- IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
negAndPos (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsNormal RegValue sym (FloatType fi)
SymInterpretedFloat sym fi
op
(SymExpr sym (BaseBVType 1)
isSubnormN, SymExpr sym (BaseBVType 1)
isSubnormP) <- IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
negAndPos (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsSubnormal RegValue sym (FloatType fi)
SymInterpretedFloat sym fi
op
(SymExpr sym (BaseBVType 1)
isZeroN, SymExpr sym (BaseBVType 1)
isZeroP) <- IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
negAndPos (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim
p
sym
ext
r
args
ret
(SymExpr sym (BaseBVType 1), SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ SymInterpretedFloat sym fi -> IO (SymExpr sym (BaseBVType 1))
callIsZero RegValue sym (FloatType fi)
SymInterpretedFloat sym fi
op
(SymExpr sym (BaseBVType 1)
-> (Natural, SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1)))
-> SymExpr sym (BaseBVType 1)
-> [(Natural, SymExpr sym (BaseBVType 1))]
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall (t :: Type -> Type) (m :: Type -> Type) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM
(\SymExpr sym (BaseBVType 1)
bits (Natural
bitNum, SymExpr sym (BaseBVType 1)
check) -> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> OverrideSim p sym ext r args ret (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ do
SymExpr sym BaseBoolType
isBitSet <- IO (SymExpr sym BaseBoolType) -> IO (SymExpr sym BaseBoolType)
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym BaseBoolType) -> IO (SymExpr sym BaseBoolType))
-> IO (SymExpr sym BaseBoolType) -> IO (SymExpr sym BaseBoolType)
forall a b. (a -> b) -> a -> b
$ sym -> Natural -> SymBV sym 32 -> IO (SymExpr sym BaseBoolType)
forall (w :: Natural).
(1 <= w) =>
sym -> Natural -> SymBV sym w -> IO (SymExpr sym BaseBoolType)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Natural -> SymBV sym w -> IO (Pred sym)
testBitBV sym
sym Natural
bitNum RegValue sym (BVType 32)
SymBV sym 32
test
SymExpr sym (BaseBVType 1)
newBit <- IO (SymExpr sym (BaseBVType 1)) -> IO (SymExpr sym (BaseBVType 1))
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym BaseBoolType
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym
-> SymExpr sym BaseBoolType
-> SymBV sym w
-> SymBV sym w
-> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> Pred sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvIte sym
sym SymExpr sym BaseBoolType
isBitSet SymExpr sym (BaseBVType 1)
check SymExpr sym (BaseBVType 1)
bv0
IO (SymExpr sym (BaseBVType 1)) -> IO (SymExpr sym (BaseBVType 1))
forall a. IO a -> IO a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1)))
-> IO (SymExpr sym (BaseBVType 1))
-> IO (SymExpr sym (BaseBVType 1))
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym (BaseBVType 1)
-> SymExpr sym (BaseBVType 1)
-> IO (SymExpr sym (BaseBVType 1))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvOrBits sym
sym SymExpr sym (BaseBVType 1)
newBit SymExpr sym (BaseBVType 1)
bits)
SymExpr sym (BaseBVType 1)
bv0
[ (Natural
0, SymExpr sym (BaseBVType 1)
isNan)
, (Natural
1, SymExpr sym (BaseBVType 1)
isNan)
, (Natural
2, SymExpr sym (BaseBVType 1)
isInfN)
, (Natural
3, SymExpr sym (BaseBVType 1)
isNormN)
, (Natural
4, SymExpr sym (BaseBVType 1)
isSubnormN)
, (Natural
5, SymExpr sym (BaseBVType 1)
isZeroN)
, (Natural
6, SymExpr sym (BaseBVType 1)
isZeroP)
, (Natural
7, SymExpr sym (BaseBVType 1)
isSubnormP)
, (Natural
8, SymExpr sym (BaseBVType 1)
isNormP)
, (Natural
9, SymExpr sym (BaseBVType 1)
isInfP)
]
callLoadRelative ::
( 1 <= w
, IsSymInterface sym
, HasPtrWidth wptr
, HasLLVMAnn sym
, ?memOpts :: MemOptions
) =>
GlobalVar Mem ->
NatRepr w ->
RegEntry sym (LLVMPointerType wptr) ->
RegEntry sym (BVType w) ->
OverrideSim p sym ext r args ret (LLVMPtr sym wptr)
callLoadRelative :: forall (w :: Natural) sym (wptr :: Natural) p ext r
(args :: Ctx CrucibleType) (ret :: CrucibleType).
(1 <= w, IsSymInterface sym, HasPtrWidth wptr, HasLLVMAnn sym,
?memOpts::MemOptions) =>
GlobalVar Mem
-> NatRepr w
-> RegEntry sym (LLVMPointerType wptr)
-> RegEntry sym (BVType w)
-> OverrideSim p sym ext r args ret (LLVMPtr sym wptr)
callLoadRelative GlobalVar Mem
mvar NatRepr w
w (RegEntry sym (LLVMPointerType wptr)
-> RegValue sym (LLVMPointerType wptr)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (LLVMPointerType wptr)
ptr) (RegEntry sym (BVType w) -> RegValue sym (BVType w)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (BVType w)
offsetInWords32) = do
MemImpl sym
mem <- GlobalVar Mem
-> OverrideSim p sym ext r args ret (RegValue sym Mem)
forall sym (tp :: CrucibleType) p ext rtp
(args :: Ctx CrucibleType) (ret :: CrucibleType).
IsSymInterface sym =>
GlobalVar tp
-> OverrideSim p sym ext rtp args ret (RegValue sym tp)
readGlobal GlobalVar Mem
mvar
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (LLVMPointer sym wptr))
-> OverrideSim p sym ext r args ret (LLVMPointer sym wptr)
forall sym p ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType) a.
(forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext rtp args ret a)
-> OverrideSim p sym ext rtp args ret a
ovrWithBackend ((forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (LLVMPointer sym wptr))
-> OverrideSim p sym ext r args ret (LLVMPointer sym wptr))
-> (forall bak.
IsSymBackend sym bak =>
bak -> OverrideSim p sym ext r args ret (LLVMPointer sym wptr))
-> OverrideSim p sym ext r args ret (LLVMPointer sym wptr)
forall a b. (a -> b) -> a -> b
$ \bak
bak -> IO (LLVMPointer sym wptr)
-> OverrideSim p sym ext r args ret (LLVMPointer sym wptr)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (LLVMPointer sym wptr)
-> OverrideSim p sym ext r args ret (LLVMPointer sym wptr))
-> IO (LLVMPointer sym wptr)
-> OverrideSim p sym ext r args ret (LLVMPointer sym wptr)
forall a b. (a -> b) -> a -> b
$ do
let sym :: sym
sym = bak -> sym
forall sym bak. HasSymInterface sym bak => bak -> sym
backendGetSym bak
bak
SymExpr sym (BaseBVType w)
bvFour <- sym -> NatRepr w -> BV w -> IO (SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
bvLit sym
sym NatRepr w
w (BV w -> IO (SymExpr sym (BaseBVType w)))
-> BV w -> IO (SymExpr sym (BaseBVType w))
forall a b. (a -> b) -> a -> b
$ NatRepr w -> Integer -> BV w
forall (w :: Natural). NatRepr w -> Integer -> BV w
BV.mkBV NatRepr w
w Integer
4
SymExpr sym (BaseBVType w)
offsetInElems <- sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUdiv sym
sym RegValue sym (BVType w)
SymExpr sym (BaseBVType w)
offsetInWords32 SymExpr sym (BaseBVType w)
bvFour
SymExpr sym (BaseBVType w)
ptrWidthBytes <-
sym -> NatRepr w -> BV w -> IO (SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
bvLit sym
sym NatRepr w
w (BV w -> IO (SymExpr sym (BaseBVType w)))
-> BV w -> IO (SymExpr sym (BaseBVType w))
forall a b. (a -> b) -> a -> b
$
BV w -> BV w -> BV w
forall (w :: Natural). BV w -> BV w -> BV w
BV.uquot
(NatRepr w -> Integer -> BV w
forall (w :: Natural). NatRepr w -> Integer -> BV w
BV.mkBV NatRepr w
w (NatRepr wptr -> Integer
forall (n :: Natural). NatRepr n -> Integer
intValue ?ptrWidth::NatRepr wptr
NatRepr wptr
?ptrWidth))
(NatRepr w -> Integer -> BV w
forall (w :: Natural). NatRepr w -> Integer -> BV w
BV.mkBV NatRepr w
w Integer
8)
SymExpr sym (BaseBVType w)
offsetInWordsPtrWidth <-
sym
-> SymExpr sym (BaseBVType w)
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym (BaseBVType w))
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvMul sym
sym SymExpr sym (BaseBVType w)
offsetInElems SymExpr sym (BaseBVType w)
ptrWidthBytes
SymExpr sym (BaseBVType wptr)
offsetInWordsPtrWidth' <-
sym
-> NatRepr w
-> NatRepr wptr
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym (BaseBVType wptr))
forall (w :: Natural) (w' :: Natural) sym.
(1 <= w, 1 <= w', IsSymInterface sym) =>
sym
-> NatRepr w
-> NatRepr w'
-> SymExpr sym (BaseBVType w)
-> IO (SymExpr sym (BaseBVType w'))
sextendBVTo sym
sym NatRepr w
w ?ptrWidth::NatRepr wptr
NatRepr wptr
?ptrWidth SymExpr sym (BaseBVType w)
offsetInWordsPtrWidth
LLVMPointer sym wptr
ptr' <- sym
-> NatRepr wptr
-> RegValue sym (LLVMPointerType wptr)
-> SymExpr sym (BaseBVType wptr)
-> IO (RegValue sym (LLVMPointerType wptr))
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym
-> NatRepr w -> LLVMPtr sym w -> SymBV sym w -> IO (LLVMPtr sym w)
ptrAdd sym
sym ?ptrWidth::NatRepr wptr
NatRepr wptr
?ptrWidth RegValue sym (LLVMPointerType wptr)
ptr SymExpr sym (BaseBVType wptr)
offsetInWordsPtrWidth'
let ty :: StorageType
ty = Bytes -> StorageType
bitvectorType (Natural -> Bytes
forall a. Integral a => a -> Bytes
bitsToBytes (NatRepr wptr -> Natural
forall (n :: Natural). NatRepr n -> Natural
natValue ?ptrWidth::NatRepr wptr
NatRepr wptr
?ptrWidth))
bak
-> MemImpl sym
-> RegValue sym (LLVMPointerType wptr)
-> StorageType
-> TypeRepr (LLVMPointerType wptr)
-> Alignment
-> IO (RegValue sym (LLVMPointerType wptr))
forall sym bak (wptr :: Natural) (tp :: CrucibleType).
(IsSymBackend sym bak, HasPtrWidth wptr, HasLLVMAnn sym,
?memOpts::MemOptions) =>
bak
-> MemImpl sym
-> LLVMPtr sym wptr
-> StorageType
-> TypeRepr tp
-> Alignment
-> IO (RegValue sym tp)
doLoad bak
bak MemImpl sym
mem RegValue sym (LLVMPointerType wptr)
LLVMPointer sym wptr
ptr' StorageType
ty TypeRepr (LLVMPointerType wptr)
forall (wptr :: Natural) (ty :: CrucibleType).
(HasPtrWidth wptr, ty ~ LLVMPointerType wptr) =>
TypeRepr ty
PtrRepr Alignment
noAlignment
callVectorReduce ::
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp)) ->
RegValue sym tp ->
RegEntry sym (VectorType tp) ->
OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce :: forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp)
reduceOp RegValue sym tp
identityVal (RegEntry sym (VectorType tp) -> RegValue sym (VectorType tp)
forall sym (tp :: CrucibleType). RegEntry sym tp -> RegValue sym tp
regValue -> RegValue sym (VectorType tp)
vec) =
IO (RegValue sym tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (RegValue sym tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp))
-> IO (RegValue sym tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
forall a b. (a -> b) -> a -> b
$ (RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> Vector (RegValue sym tp)
-> IO (RegValue sym tp)
forall (m :: Type -> Type) a b.
Monad m =>
(a -> b -> m a) -> a -> Vector b -> m a
V.foldM RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp)
reduceOp RegValue sym tp
identityVal Vector (RegValue sym tp)
RegValue sym (VectorType tp)
vec
callVectorReduceAdd ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceAdd :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceAdd NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
zero <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvZero sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvAdd sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
zero RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceMul ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceMul :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceMul NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
one <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvOne sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvMul sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
one RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceAnd ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceAnd :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceAnd NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
zero <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvZero sym
sym NatRepr intSz
intSz
SymBV sym intSz
ones <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> SymBV sym intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> IO (SymBV sym w)
bvNotBits sym
sym SymBV sym intSz
zero
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvAndBits sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
ones RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceOr ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceOr :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceOr NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
zero <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvZero sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvOrBits sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
zero RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceXor ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceXor :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceXor NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
zero <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural) sym.
(1 <= w, IsExprBuilder sym) =>
sym -> NatRepr w -> IO (SymBV sym w)
bvZero sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvXorBits sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
zero RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceSmax ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceSmax :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceSmax NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
smin <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
minSignedBV sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvSmax sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
smin RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceSmin ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceSmin :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceSmin NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
smax <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
maxSignedBV sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvSmin sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
smax RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceUmax ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceUmax :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceUmax NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
umin <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
minUnsignedBV sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUmax sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
umin RegEntry sym (VectorType (BVType intSz))
vec
callVectorReduceUmin ::
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz ->
RegEntry sym (VectorType (BVType intSz)) ->
OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceUmin :: forall sym (intSz :: Natural) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(IsSymInterface sym, 1 <= intSz) =>
NatRepr intSz
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
callVectorReduceUmin NatRepr intSz
intSz RegEntry sym (VectorType (BVType intSz))
vec = do
sym
sym <- OverrideSim p sym ext r args ret sym
forall p sym ext rtp (args :: Ctx CrucibleType)
(ret :: CrucibleType).
OverrideSim p sym ext rtp args ret sym
getSymInterface
SymBV sym intSz
umax <- IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a. IO a -> OverrideSim p sym ext r args ret a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz))
-> IO (SymBV sym intSz)
-> OverrideSim p sym ext r args ret (SymBV sym intSz)
forall a b. (a -> b) -> a -> b
$ sym -> NatRepr intSz -> IO (SymBV sym intSz)
forall (w :: Natural).
(1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> IO (SymBV sym w)
maxUnsignedBV sym
sym NatRepr intSz
intSz
(RegValue sym (BVType intSz)
-> RegValue sym (BVType intSz) -> IO (RegValue sym (BVType intSz)))
-> RegValue sym (BVType intSz)
-> RegEntry sym (VectorType (BVType intSz))
-> OverrideSim p sym ext r args ret (RegValue sym (BVType intSz))
forall sym (tp :: CrucibleType) p ext r (args :: Ctx CrucibleType)
(ret :: CrucibleType).
(RegValue sym tp -> RegValue sym tp -> IO (RegValue sym tp))
-> RegValue sym tp
-> RegEntry sym (VectorType tp)
-> OverrideSim p sym ext r args ret (RegValue sym tp)
callVectorReduce (sym -> SymBV sym intSz -> SymBV sym intSz -> IO (SymBV sym intSz)
forall sym (w :: Natural).
(IsExprBuilder sym, 1 <= w) =>
sym -> SymBV sym w -> SymBV sym w -> IO (SymBV sym w)
bvUmin sym
sym) RegValue sym (BVType intSz)
SymBV sym intSz
umax RegEntry sym (VectorType (BVType intSz))
vec