Safe Haskell | None |
---|---|
Language | Haskell2010 |
Copilot.Verifier.Log
Synopsis
- type SupportsCopilotLogMessage msgs = ?injectCopilotLogMessage :: CopilotLogMessage -> msgs
- data CopilotLogMessage where
- GeneratedCFile :: FilePath -> CopilotLogMessage
- CompiledBitcodeFile :: String -> FilePath -> CopilotLogMessage
- TranslatedToCrucible :: CopilotLogMessage
- GeneratingProofState :: CopilotLogMessage
- ComputingConditions :: VerificationStep -> CopilotLogMessage
- ProvingConditions :: VerificationStep -> CopilotLogMessage
- AllGoalsProved :: CopilotLogMessage
- OnlySomeGoalsProved :: Integer -> Integer -> CopilotLogMessage
- SuccessfulProofSummary :: FilePath -> Integer -> Integer -> CopilotLogMessage
- NoisyVerbositySuggestion :: CopilotLogMessage
- StreamValueEqualityProofGoal :: forall sym copilotType (crucibleType :: CrucibleType). IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> StreamValueEquality sym copilotType crucibleType -> CopilotLogMessage
- TriggersInvokedCorrespondinglyProofGoal :: forall sym. IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> TriggersInvokedCorrespondingly sym -> CopilotLogMessage
- TriggerArgumentEqualityProofGoal :: forall sym copilotType (crucibleType :: CrucibleType). IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> TriggerArgumentEquality sym copilotType crucibleType -> CopilotLogMessage
- RingBufferLoadProofGoal :: forall sym copilotType (crucibleType :: CrucibleType). IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> RingBufferLoad sym copilotType crucibleType -> CopilotLogMessage
- RingBufferIndexLoadProofGoal :: forall sym. IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> RingBufferIndexLoad sym -> CopilotLogMessage
- PointerArgumentLoadProofGoal :: forall sym copilotType (crucibleType :: CrucibleType). IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> PointerArgumentLoad sym copilotType crucibleType -> CopilotLogMessage
- AccessorFunctionLoadProofGoal :: forall sym. IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> AccessorFunctionLoad sym -> CopilotLogMessage
- GuardFunctionLoadProofGoal :: forall sym. IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> GuardFunctionLoad sym -> CopilotLogMessage
- UnknownFunctionLoadProofGoal :: forall sym. IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> UnknownFunctionLoad sym -> CopilotLogMessage
- LLVMBadBehaviorCheckProofGoal :: forall sym. IsSymExprBuilder sym => VerificationStep -> Integer -> Integer -> LLVMBadBehaviorCheck sym -> CopilotLogMessage
- data VerificationStep
- data StateRelationStep
- data VerifierAssertion sym
- = StreamValueEqualityAssertion (SomeSome (StreamValueEquality sym))
- | TriggersInvokedCorrespondinglyAssertion (TriggersInvokedCorrespondingly sym)
- | TriggerArgumentEqualityAssertion (SomeSome (TriggerArgumentEquality sym))
- | RingBufferLoadAssertion (SomeSome (RingBufferLoad sym))
- | RingBufferIndexLoadAssertion (RingBufferIndexLoad sym)
- | PointerArgumentLoadAssertion (SomeSome (PointerArgumentLoad sym))
- | AccessorFunctionLoadAssertion (AccessorFunctionLoad sym)
- | GuardFunctionLoadAssertion (GuardFunctionLoad sym)
- | UnknownFunctionLoadAssertion (UnknownFunctionLoad sym)
- | LLVMBadBehaviorCheckAssertion (LLVMBadBehaviorCheck sym)
- data SomeSome (f :: j -> k -> Type) where
- data StreamValueEquality sym copilotType (crucibleType :: CrucibleType) where
- StreamValueEquality :: forall sym copilotType (crucibleType :: CrucibleType). sym -> StateRelationStep -> ProgramLoc -> Text -> Integer -> Integer -> Type copilotType -> XExpr sym -> TypeRepr crucibleType -> RegValue sym crucibleType -> StreamValueEquality sym copilotType crucibleType
- data TriggersInvokedCorrespondingly sym where
- TriggersInvokedCorrespondingly :: forall sym. ProgramLoc -> Name -> SymNat sym -> SymNat sym -> TriggersInvokedCorrespondingly sym
- data TriggerArgumentEquality sym copilotType (crucibleType :: CrucibleType) where
- TriggerArgumentEquality :: forall sym copilotType (crucibleType :: CrucibleType). sym -> ProgramLoc -> Name -> Integer -> Type copilotType -> XExpr sym -> TypeRepr crucibleType -> RegValue sym crucibleType -> TriggerArgumentEquality sym copilotType crucibleType
- data RingBufferLoad sym copilotType (crucibleType :: CrucibleType) where
- RingBufferLoad :: forall sym copilotType (crucibleType :: CrucibleType). sym -> StateRelationStep -> ProgramLoc -> Text -> Integer -> Integer -> Type copilotType -> TypeRepr crucibleType -> Pred sym -> RingBufferLoad sym copilotType crucibleType
- data RingBufferIndexLoad sym where
- RingBufferIndexLoad :: forall sym. sym -> StateRelationStep -> ProgramLoc -> Text -> Pred sym -> RingBufferIndexLoad sym
- data PointerArgumentLoad sym copilotType (crucibleType :: CrucibleType) where
- PointerArgumentLoad :: forall sym copilotType (crucibleType :: CrucibleType). sym -> ProgramLoc -> Type copilotType -> TypeRepr crucibleType -> Pred sym -> PointerArgumentLoad sym copilotType crucibleType
- data AccessorFunctionLoad sym where
- AccessorFunctionLoad :: forall sym. sym -> ProgramLoc -> FunctionName -> Pred sym -> AccessorFunctionLoad sym
- data GuardFunctionLoad sym where
- GuardFunctionLoad :: forall sym. sym -> ProgramLoc -> FunctionName -> Pred sym -> GuardFunctionLoad sym
- data UnknownFunctionLoad sym where
- UnknownFunctionLoad :: forall sym. sym -> ProgramLoc -> FunctionName -> Pred sym -> UnknownFunctionLoad sym
- data LLVMBadBehaviorCheck sym where
- LLVMBadBehaviorCheck :: forall sym. sym -> ProgramLoc -> CallStack -> BadBehavior sym -> Pred sym -> LLVMBadBehaviorCheck sym
- sayCopilot :: (Logs msgs, SupportsCopilotLogMessage msgs) => CopilotLogMessage -> IO ()
- copilotLogMessageToSayWhat :: CopilotLogMessage -> SayWhat
Documentation
type SupportsCopilotLogMessage msgs = ?injectCopilotLogMessage :: CopilotLogMessage -> msgs Source #
data CopilotLogMessage where Source #
Constructors
Instances
ToJSON CopilotLogMessage Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: CopilotLogMessage -> Value # toEncoding :: CopilotLogMessage -> Encoding # toJSONList :: [CopilotLogMessage] -> Value # toEncodingList :: [CopilotLogMessage] -> Encoding # omitField :: CopilotLogMessage -> Bool # |
data VerificationStep Source #
Constructors
InitialState | |
StepBisimulation |
Instances
ToJSON VerificationStep Source # | |||||
Defined in Copilot.Verifier.Log Methods toJSON :: VerificationStep -> Value # toEncoding :: VerificationStep -> Encoding # toJSONList :: [VerificationStep] -> Value # toEncodingList :: [VerificationStep] -> Encoding # omitField :: VerificationStep -> Bool # | |||||
Generic VerificationStep Source # | |||||
Defined in Copilot.Verifier.Log Associated Types
Methods from :: VerificationStep -> Rep VerificationStep x # to :: Rep VerificationStep x -> VerificationStep # | |||||
type Rep VerificationStep Source # | |||||
Defined in Copilot.Verifier.Log |
data StateRelationStep Source #
At what step of the proof are we checking the state relation? We record
this so that we can better distinguish between transition step–related
proof goals that arise before or after calling the step()
function.
Constructors
InitialStateRelation | Check the state relation for the initial state. |
PreStepStateRelation | During the transition step of the proof, check the state relation
before calling the |
PostStepStateRelation | During the transition step of the proof, check the state relation
after calling the |
Instances
data VerifierAssertion sym Source #
Types of assertions that the verifier can make, which will count towards the total number of proof goals.
Constructors
StreamValueEqualityAssertion (SomeSome (StreamValueEquality sym)) | |
TriggersInvokedCorrespondinglyAssertion (TriggersInvokedCorrespondingly sym) | |
TriggerArgumentEqualityAssertion (SomeSome (TriggerArgumentEquality sym)) | |
RingBufferLoadAssertion (SomeSome (RingBufferLoad sym)) | |
RingBufferIndexLoadAssertion (RingBufferIndexLoad sym) | |
PointerArgumentLoadAssertion (SomeSome (PointerArgumentLoad sym)) | |
AccessorFunctionLoadAssertion (AccessorFunctionLoad sym) | |
GuardFunctionLoadAssertion (GuardFunctionLoad sym) | |
UnknownFunctionLoadAssertion (UnknownFunctionLoad sym) | |
LLVMBadBehaviorCheckAssertion (LLVMBadBehaviorCheck sym) |
data SomeSome (f :: j -> k -> Type) where Source #
Like Some
in parameterized-utils
, but existentially closing over two
type parameters instead of just one.
data StreamValueEquality sym copilotType (crucibleType :: CrucibleType) where Source #
An assertion that an element in a Copilot stream is equal to the corresponding element in a C ring buffer.
Constructors
StreamValueEquality | |
Fields
|
Instances
ToJSON (StreamValueEquality sym copilotType crucibleType) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: StreamValueEquality sym copilotType crucibleType -> Value # toEncoding :: StreamValueEquality sym copilotType crucibleType -> Encoding # toJSONList :: [StreamValueEquality sym copilotType crucibleType] -> Value # toEncodingList :: [StreamValueEquality sym copilotType crucibleType] -> Encoding # omitField :: StreamValueEquality sym copilotType crucibleType -> Bool # |
data TriggersInvokedCorrespondingly sym where Source #
An assertion that, given a Copilot trigger stream and its corresponding C trigger function on a particular time step, either both fired at the same time or both did not fire at all.
Constructors
TriggersInvokedCorrespondingly | |
Fields
|
Instances
ToJSON (TriggersInvokedCorrespondingly sym) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: TriggersInvokedCorrespondingly sym -> Value # toEncoding :: TriggersInvokedCorrespondingly sym -> Encoding # toJSONList :: [TriggersInvokedCorrespondingly sym] -> Value # toEncodingList :: [TriggersInvokedCorrespondingly sym] -> Encoding # omitField :: TriggersInvokedCorrespondingly sym -> Bool # |
data TriggerArgumentEquality sym copilotType (crucibleType :: CrucibleType) where Source #
An assertion that an argument to a Copilot trigger is equal to the corresponding argument to a C trigger function.
Constructors
TriggerArgumentEquality | |
Fields
|
Instances
ToJSON (TriggerArgumentEquality sym copilotType crucibleType) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: TriggerArgumentEquality sym copilotType crucibleType -> Value # toEncoding :: TriggerArgumentEquality sym copilotType crucibleType -> Encoding # toJSONList :: [TriggerArgumentEquality sym copilotType crucibleType] -> Value # toEncodingList :: [TriggerArgumentEquality sym copilotType crucibleType] -> Encoding # omitField :: TriggerArgumentEquality sym copilotType crucibleType -> Bool # |
data RingBufferLoad sym copilotType (crucibleType :: CrucibleType) where Source #
An assertion that a load from a ring buffer in C is valid.
Constructors
RingBufferLoad | |
Fields
|
Instances
ToJSON (RingBufferLoad sym copilotType crucibleType) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: RingBufferLoad sym copilotType crucibleType -> Value # toEncoding :: RingBufferLoad sym copilotType crucibleType -> Encoding # toJSONList :: [RingBufferLoad sym copilotType crucibleType] -> Value # toEncodingList :: [RingBufferLoad sym copilotType crucibleType] -> Encoding # omitField :: RingBufferLoad sym copilotType crucibleType -> Bool # |
data RingBufferIndexLoad sym where Source #
An assertion that a load from a global variable representing a ring buffer's index in C is valid.
Constructors
RingBufferIndexLoad | |
Fields
|
Instances
ToJSON (RingBufferIndexLoad sym) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: RingBufferIndexLoad sym -> Value # toEncoding :: RingBufferIndexLoad sym -> Encoding # toJSONList :: [RingBufferIndexLoad sym] -> Value # toEncodingList :: [RingBufferIndexLoad sym] -> Encoding # omitField :: RingBufferIndexLoad sym -> Bool # |
data PointerArgumentLoad sym copilotType (crucibleType :: CrucibleType) where Source #
An assertion that a load from a pointer argument to a trigger function in C is valid.
Constructors
PointerArgumentLoad | |
Fields
|
Instances
ToJSON (PointerArgumentLoad sym copilotType crucibleType) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: PointerArgumentLoad sym copilotType crucibleType -> Value # toEncoding :: PointerArgumentLoad sym copilotType crucibleType -> Encoding # toJSONList :: [PointerArgumentLoad sym copilotType crucibleType] -> Value # toEncodingList :: [PointerArgumentLoad sym copilotType crucibleType] -> Encoding # omitField :: PointerArgumentLoad sym copilotType crucibleType -> Bool # |
data AccessorFunctionLoad sym where Source #
An assertion that a load occurring from somewhere in a stream accessor
function in C (e.g., s0_get
) is valid. This is a somewhat imprecise
assertion, as it doesn't identify why the load occurs. (Most likely, it
happens because of an array index.)
Constructors
AccessorFunctionLoad | |
Fields
|
Instances
ToJSON (AccessorFunctionLoad sym) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: AccessorFunctionLoad sym -> Value # toEncoding :: AccessorFunctionLoad sym -> Encoding # toJSONList :: [AccessorFunctionLoad sym] -> Value # toEncodingList :: [AccessorFunctionLoad sym] -> Encoding # omitField :: AccessorFunctionLoad sym -> Bool # |
data GuardFunctionLoad sym where Source #
An assertion that a load occurring from somewhere in a trigger guard
function in C (e.g., even_guard
) is valid. This is a somewhat imprecise
assertion, as it doesn't identify why the load occurs. (Most likely, it
happens because of an array index.)
Constructors
GuardFunctionLoad | |
Fields
|
Instances
ToJSON (GuardFunctionLoad sym) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: GuardFunctionLoad sym -> Value # toEncoding :: GuardFunctionLoad sym -> Encoding # toJSONList :: [GuardFunctionLoad sym] -> Value # toEncodingList :: [GuardFunctionLoad sym] -> Encoding # omitField :: GuardFunctionLoad sym -> Bool # |
data UnknownFunctionLoad sym where Source #
An assertion that a load occurring in some function is valid. If you see this assertion, it is because the heuristics used to identify where load-related assertions come from could not identify a more precise cause for a load.
Constructors
UnknownFunctionLoad | |
Fields
|
Instances
ToJSON (UnknownFunctionLoad sym) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: UnknownFunctionLoad sym -> Value # toEncoding :: UnknownFunctionLoad sym -> Encoding # toJSONList :: [UnknownFunctionLoad sym] -> Value # toEncodingList :: [UnknownFunctionLoad sym] -> Encoding # omitField :: UnknownFunctionLoad sym -> Bool # |
data LLVMBadBehaviorCheck sym where Source #
An assertion that checks that some form of bad behavior in LLVM does not occur. Bad behavior includes both undefined behavior and memory unsafety.
Constructors
LLVMBadBehaviorCheck | |
Fields
|
Instances
ToJSON (LLVMBadBehaviorCheck sym) Source # | |
Defined in Copilot.Verifier.Log Methods toJSON :: LLVMBadBehaviorCheck sym -> Value # toEncoding :: LLVMBadBehaviorCheck sym -> Encoding # toJSONList :: [LLVMBadBehaviorCheck sym] -> Value # toEncodingList :: [LLVMBadBehaviorCheck sym] -> Encoding # omitField :: LLVMBadBehaviorCheck sym -> Bool # |
sayCopilot :: (Logs msgs, SupportsCopilotLogMessage msgs) => CopilotLogMessage -> IO () Source #