{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeAbstractions #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.TP.Utils (
TP, runTP, runTPWith, Proof(..), ProofObj(..), assumptionFromProof, sorry, quickCheckProof
, startTP, finishTP, getTPState, getTPConfig, tpGetNextUnique, TPState(..), TPStats(..), RootOfTrust(..)
, TPProofContext(..), message, updStats, rootOfTrust, concludeModulo
, ProofTree(..), TPUnique(..), showProofTree, showProofTreeHTML, shortProofName
, withProofCache
, tpQuiet, tpRibbon, tpStats, tpCache
) where
import Control.Monad.Reader (ReaderT, runReaderT, MonadReader, ask, liftIO)
import Control.Monad.Trans (MonadIO)
import Data.Time (NominalDiffTime)
import Data.Tree
import Data.Tree.View
import Data.Proxy
import Data.Typeable (typeOf, TypeRep)
import Data.Char (isSpace)
import Data.List (intercalate, isPrefixOf, isSuffixOf, isInfixOf, nubBy, partition, sort)
import Data.Int (Int64)
import Data.SBV.Utils.Lib (unQuote)
import System.IO (hFlush, stdout)
import System.Random (randomIO)
import Data.SBV.Core.Data (SBool, Forall(..), quantifiedBool)
import Data.SBV.Core.Model (label)
import Data.SBV.Core.Symbolic (SMTConfig, TPOptions(..))
import Data.SBV.Provers.Prover (defaultSMTCfg, SMTConfig(..))
import Data.SBV.Utils.TDiff (showTDiff, timeIf)
import Control.DeepSeq (NFData(rnf))
import Data.IORef
import GHC.Generics
import Data.Dynamic
import qualified Data.Map as Map
import Data.Map (Map)
data TPStats = TPStats { TPStats -> Int
noOfCheckSats :: Int
, TPStats -> NominalDiffTime
solverElapsed :: NominalDiffTime
, TPStats -> NominalDiffTime
qcElapsed :: NominalDiffTime
}
data TPState = TPState { TPState -> IORef TPStats
stats :: IORef TPStats
, TPState -> IORef (Map (String, TypeRep) ProofObj)
proofCache :: IORef (Map (String, TypeRep) ProofObj)
, TPState -> SMTConfig
config :: SMTConfig
}
newtype TP a = TP (ReaderT TPState IO a)
deriving newtype (Functor TP
Functor TP =>
(forall a. a -> TP a)
-> (forall a b. TP (a -> b) -> TP a -> TP b)
-> (forall a b c. (a -> b -> c) -> TP a -> TP b -> TP c)
-> (forall a b. TP a -> TP b -> TP b)
-> (forall a b. TP a -> TP b -> TP a)
-> Applicative TP
forall a. a -> TP a
forall a b. TP a -> TP b -> TP a
forall a b. TP a -> TP b -> TP b
forall a b. TP (a -> b) -> TP a -> TP b
forall a b c. (a -> b -> c) -> TP a -> TP b -> TP c
forall (f :: * -> *).
Functor f =>
(forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
$cpure :: forall a. a -> TP a
pure :: forall a. a -> TP a
$c<*> :: forall a b. TP (a -> b) -> TP a -> TP b
<*> :: forall a b. TP (a -> b) -> TP a -> TP b
$cliftA2 :: forall a b c. (a -> b -> c) -> TP a -> TP b -> TP c
liftA2 :: forall a b c. (a -> b -> c) -> TP a -> TP b -> TP c
$c*> :: forall a b. TP a -> TP b -> TP b
*> :: forall a b. TP a -> TP b -> TP b
$c<* :: forall a b. TP a -> TP b -> TP a
<* :: forall a b. TP a -> TP b -> TP a
Applicative, (forall a b. (a -> b) -> TP a -> TP b)
-> (forall a b. a -> TP b -> TP a) -> Functor TP
forall a b. a -> TP b -> TP a
forall a b. (a -> b) -> TP a -> TP b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> TP a -> TP b
fmap :: forall a b. (a -> b) -> TP a -> TP b
$c<$ :: forall a b. a -> TP b -> TP a
<$ :: forall a b. a -> TP b -> TP a
Functor, Applicative TP
Applicative TP =>
(forall a b. TP a -> (a -> TP b) -> TP b)
-> (forall a b. TP a -> TP b -> TP b)
-> (forall a. a -> TP a)
-> Monad TP
forall a. a -> TP a
forall a b. TP a -> TP b -> TP b
forall a b. TP a -> (a -> TP b) -> TP b
forall (m :: * -> *).
Applicative m =>
(forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
$c>>= :: forall a b. TP a -> (a -> TP b) -> TP b
>>= :: forall a b. TP a -> (a -> TP b) -> TP b
$c>> :: forall a b. TP a -> TP b -> TP b
>> :: forall a b. TP a -> TP b -> TP b
$creturn :: forall a. a -> TP a
return :: forall a. a -> TP a
Monad, Monad TP
Monad TP => (forall a. IO a -> TP a) -> MonadIO TP
forall a. IO a -> TP a
forall (m :: * -> *).
Monad m =>
(forall a. IO a -> m a) -> MonadIO m
$cliftIO :: forall a. IO a -> TP a
liftIO :: forall a. IO a -> TP a
MonadIO, MonadReader TPState, Monad TP
Monad TP => (forall a. String -> TP a) -> MonadFail TP
forall a. String -> TP a
forall (m :: * -> *).
Monad m =>
(forall a. String -> m a) -> MonadFail m
$cfail :: forall a. String -> TP a
fail :: forall a. String -> TP a
MonadFail)
withProofCache :: forall a. Typeable a => String -> TP (Proof a) -> TP (Proof a)
withProofCache :: forall a. Typeable a => String -> TP (Proof a) -> TP (Proof a)
withProofCache String
nm TP (Proof a)
genProof = do
TPState{IORef (Map (String, TypeRep) ProofObj)
proofCache :: TPState -> IORef (Map (String, TypeRep) ProofObj)
proofCache :: IORef (Map (String, TypeRep) ProofObj)
proofCache, config :: TPState -> SMTConfig
config = cfg :: SMTConfig
cfg@SMTConfig {tpOptions :: SMTConfig -> TPOptions
tpOptions = TPOptions {Bool
cacheProofs :: Bool
cacheProofs :: TPOptions -> Bool
cacheProofs}}} <- TP TPState
getTPState
let key :: (String, TypeRep)
key = (String
nm, Proxy a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a))
if Bool -> Bool
not Bool
cacheProofs
then TP (Proof a)
genProof
else do Map (String, TypeRep) ProofObj
cache <- IO (Map (String, TypeRep) ProofObj)
-> TP (Map (String, TypeRep) ProofObj)
forall a. IO a -> TP a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Map (String, TypeRep) ProofObj)
-> TP (Map (String, TypeRep) ProofObj))
-> IO (Map (String, TypeRep) ProofObj)
-> TP (Map (String, TypeRep) ProofObj)
forall a b. (a -> b) -> a -> b
$ IORef (Map (String, TypeRep) ProofObj)
-> IO (Map (String, TypeRep) ProofObj)
forall a. IORef a -> IO a
readIORef IORef (Map (String, TypeRep) ProofObj)
proofCache
case (String, TypeRep)
key (String, TypeRep)
-> Map (String, TypeRep) ProofObj -> Maybe ProofObj
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map (String, TypeRep) ProofObj
cache of
Just ProofObj
prf -> do IO () -> TP ()
forall a. IO a -> TP a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> TP ()) -> IO () -> TP ()
forall a b. (a -> b) -> a -> b
$ do Int
tab <- SMTConfig -> Bool -> String -> Int -> TPProofContext -> IO Int
startTP SMTConfig
cfg Bool
False String
"Cached" Int
0 (String -> [ProofObj] -> TPProofContext
TPProofOneShot String
nm [])
SMTConfig
-> String
-> (Int, Maybe NominalDiffTime)
-> [NominalDiffTime]
-> IO ()
finishTP SMTConfig
cfg String
"Q.E.D." (Int
tab, Maybe NominalDiffTime
forall a. Maybe a
Nothing) []
Proof a -> TP (Proof a)
forall a. a -> TP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Proof a -> TP (Proof a)) -> Proof a -> TP (Proof a)
forall a b. (a -> b) -> a -> b
$ ProofObj -> Proof a
forall a. ProofObj -> Proof a
Proof ProofObj
prf{isCached = True}
Maybe ProofObj
Nothing -> do Proof a
p <- TP (Proof a)
genProof
IO () -> TP ()
forall a. IO a -> TP a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> TP ()) -> IO () -> TP ()
forall a b. (a -> b) -> a -> b
$ IORef (Map (String, TypeRep) ProofObj)
-> (Map (String, TypeRep) ProofObj
-> Map (String, TypeRep) ProofObj)
-> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef (Map (String, TypeRep) ProofObj)
proofCache ((String, TypeRep)
-> ProofObj
-> Map (String, TypeRep) ProofObj
-> Map (String, TypeRep) ProofObj
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (String, TypeRep)
key (Proof a -> ProofObj
forall a. Proof a -> ProofObj
proofOf Proof a
p))
Proof a -> TP (Proof a)
forall a. a -> TP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proof a
p
data TPProofContext = TPProofOneShot String
[ProofObj]
| TPProofStep Bool
String
[String]
[String]
runTP :: TP a -> IO a
runTP :: forall a. TP a -> IO a
runTP = SMTConfig -> TP a -> IO a
forall a. SMTConfig -> TP a -> IO a
runTPWith SMTConfig
defaultSMTCfg
runTPWith :: SMTConfig -> TP a -> IO a
runTPWith :: forall a. SMTConfig -> TP a -> IO a
runTPWith cfg :: SMTConfig
cfg@SMTConfig{tpOptions :: SMTConfig -> TPOptions
tpOptions = TPOptions{Bool
printStats :: Bool
printStats :: TPOptions -> Bool
printStats}} (TP ReaderT TPState IO a
f) = do
IORef TPStats
rStats <- TPStats -> IO (IORef TPStats)
forall a. a -> IO (IORef a)
newIORef (TPStats -> IO (IORef TPStats)) -> TPStats -> IO (IORef TPStats)
forall a b. (a -> b) -> a -> b
$ TPStats { noOfCheckSats :: Int
noOfCheckSats = Int
0, solverElapsed :: NominalDiffTime
solverElapsed = NominalDiffTime
0, qcElapsed :: NominalDiffTime
qcElapsed = NominalDiffTime
0 }
IORef (Map (String, TypeRep) ProofObj)
rCache <- Map (String, TypeRep) ProofObj
-> IO (IORef (Map (String, TypeRep) ProofObj))
forall a. a -> IO (IORef a)
newIORef Map (String, TypeRep) ProofObj
forall k a. Map k a
Map.empty
(Maybe NominalDiffTime
mbT, a
r) <- Bool -> IO a -> IO (Maybe NominalDiffTime, a)
forall (m :: * -> *) a.
MonadIO m =>
Bool -> m a -> m (Maybe NominalDiffTime, a)
timeIf Bool
printStats (IO a -> IO (Maybe NominalDiffTime, a))
-> IO a -> IO (Maybe NominalDiffTime, a)
forall a b. (a -> b) -> a -> b
$ ReaderT TPState IO a -> TPState -> IO a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT TPState IO a
f TPState {config :: SMTConfig
config = SMTConfig
cfg, stats :: IORef TPStats
stats = IORef TPStats
rStats, proofCache :: IORef (Map (String, TypeRep) ProofObj)
proofCache = IORef (Map (String, TypeRep) ProofObj)
rCache}
case Maybe NominalDiffTime
mbT of
Maybe NominalDiffTime
Nothing -> () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just NominalDiffTime
t -> do TPStats Int
noOfCheckSats NominalDiffTime
solverTime NominalDiffTime
qcElapsed <- IORef TPStats -> IO TPStats
forall a. IORef a -> IO a
readIORef IORef TPStats
rStats
let stats :: [(String, String)]
stats = [ (String
"SBV", NominalDiffTime -> String
showTDiff (NominalDiffTime
t NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall a. Num a => a -> a -> a
- NominalDiffTime
solverTime NominalDiffTime -> NominalDiffTime -> NominalDiffTime
forall a. Num a => a -> a -> a
- NominalDiffTime
qcElapsed))
, (String
"Solver", NominalDiffTime -> String
showTDiff NominalDiffTime
solverTime)
, (String
"QC", NominalDiffTime -> String
showTDiff NominalDiffTime
qcElapsed)
, (String
"Total", NominalDiffTime -> String
showTDiff NominalDiffTime
t)
, (String
"Decisions", Int -> String
forall a. Show a => a -> String
show Int
noOfCheckSats)
]
SMTConfig -> String -> IO ()
forall (m :: * -> *). MonadIO m => SMTConfig -> String -> m ()
message SMTConfig
cfg (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Char
'[' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String
k String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
v | (String
k, String
v) <- [(String, String)]
stats] String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]\n"
a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
r
getTPState :: TP TPState
getTPState :: TP TPState
getTPState = TP TPState
forall r (m :: * -> *). MonadReader r m => m r
ask
tpGetNextUnique :: TP TPUnique
tpGetNextUnique :: TP TPUnique
tpGetNextUnique = Int64 -> TPUnique
TPUser (Int64 -> TPUnique) -> TP Int64 -> TP TPUnique
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Int64 -> TP Int64
forall a. IO a -> TP a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Int64
forall a (m :: * -> *). (Random a, MonadIO m) => m a
randomIO
getTPConfig :: TP SMTConfig
getTPConfig :: TP SMTConfig
getTPConfig = TPState -> SMTConfig
config (TPState -> SMTConfig) -> TP TPState -> TP SMTConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TP TPState
getTPState
updStats :: MonadIO m => TPState -> (TPStats -> TPStats) -> m ()
updStats :: forall (m :: * -> *).
MonadIO m =>
TPState -> (TPStats -> TPStats) -> m ()
updStats TPState{IORef TPStats
stats :: TPState -> IORef TPStats
stats :: IORef TPStats
stats} TPStats -> TPStats
u = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ IORef TPStats -> (TPStats -> TPStats) -> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef' IORef TPStats
stats TPStats -> TPStats
u
message :: MonadIO m => SMTConfig -> String -> m ()
message :: forall (m :: * -> *). MonadIO m => SMTConfig -> String -> m ()
message SMTConfig{tpOptions :: SMTConfig -> TPOptions
tpOptions = TPOptions{Bool
quiet :: Bool
quiet :: TPOptions -> Bool
quiet}} String
s
| Bool
quiet = () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
| Bool
True = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ String -> IO ()
putStr String
s
startTP :: SMTConfig -> Bool -> String -> Int -> TPProofContext -> IO Int
startTP :: SMTConfig -> Bool -> String -> Int -> TPProofContext -> IO Int
startTP SMTConfig
cfg Bool
newLine String
what Int
level TPProofContext
ctx = do SMTConfig -> String -> IO ()
forall (m :: * -> *). MonadIO m => SMTConfig -> String -> m ()
message SMTConfig
cfg (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
line String -> String -> String
forall a. [a] -> [a] -> [a]
++ if Bool
newLine then String
"\n" else String
""
Handle -> IO ()
hFlush Handle
stdout
Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
line)
where nm :: String
nm = case TPProofContext
ctx of
TPProofOneShot String
n [ProofObj]
_ -> String
n
TPProofStep Bool
_ String
_ [String]
hs [String]
ss -> String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." [String]
ss String -> String -> String
forall a. [a] -> [a] -> [a]
++ [String] -> String
userHints [String]
hs
tab :: Int
tab = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
level
line :: String
line = Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
tab Char
' ' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
what String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm
userHints :: [String] -> String
userHints [] = String
""
userHints [String]
ss = String
" (" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
ss String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
finishTP :: SMTConfig -> String -> (Int, Maybe NominalDiffTime) -> [NominalDiffTime] -> IO ()
finishTP :: SMTConfig
-> String
-> (Int, Maybe NominalDiffTime)
-> [NominalDiffTime]
-> IO ()
finishTP cfg :: SMTConfig
cfg@SMTConfig{tpOptions :: SMTConfig -> TPOptions
tpOptions = TPOptions{Int
ribbonLength :: Int
ribbonLength :: TPOptions -> Int
ribbonLength}} String
what (Int
skip, Maybe NominalDiffTime
mbT) [NominalDiffTime]
extraTiming =
SMTConfig -> String -> IO ()
forall (m :: * -> *). MonadIO m => SMTConfig -> String -> m ()
message SMTConfig
cfg (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
ribbonLength Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
skip) Char
' ' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
what String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
timing String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
extras String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
where timing :: String
timing = String
-> (NominalDiffTime -> String) -> Maybe NominalDiffTime -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ((Char
' ' Char -> String -> String
forall a. a -> [a] -> [a]
:) (String -> String)
-> (NominalDiffTime -> String) -> NominalDiffTime -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> String
mkTiming) Maybe NominalDiffTime
mbT
extras :: String
extras = (NominalDiffTime -> String) -> [NominalDiffTime] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap NominalDiffTime -> String
mkTiming [NominalDiffTime]
extraTiming
mkTiming :: NominalDiffTime -> String
mkTiming NominalDiffTime
t = Char
'[' Char -> String -> String
forall a. a -> [a] -> [a]
: NominalDiffTime -> String
showTDiff NominalDiffTime
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
data TPUnique = TPInternal
| TPSorry
| TPQC
| TPUser Int64
deriving (TPUnique -> ()
(TPUnique -> ()) -> NFData TPUnique
forall a. (a -> ()) -> NFData a
$crnf :: TPUnique -> ()
rnf :: TPUnique -> ()
NFData, (forall x. TPUnique -> Rep TPUnique x)
-> (forall x. Rep TPUnique x -> TPUnique) -> Generic TPUnique
forall x. Rep TPUnique x -> TPUnique
forall x. TPUnique -> Rep TPUnique x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TPUnique -> Rep TPUnique x
from :: forall x. TPUnique -> Rep TPUnique x
$cto :: forall x. Rep TPUnique x -> TPUnique
to :: forall x. Rep TPUnique x -> TPUnique
Generic, TPUnique -> TPUnique -> Bool
(TPUnique -> TPUnique -> Bool)
-> (TPUnique -> TPUnique -> Bool) -> Eq TPUnique
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TPUnique -> TPUnique -> Bool
== :: TPUnique -> TPUnique -> Bool
$c/= :: TPUnique -> TPUnique -> Bool
/= :: TPUnique -> TPUnique -> Bool
Eq)
newtype Proof a = Proof { forall a. Proof a -> ProofObj
proofOf :: ProofObj
}
assumptionFromProof :: Proof a -> SBool
assumptionFromProof :: forall a. Proof a -> SBV Bool
assumptionFromProof = ProofObj -> SBV Bool
getObjProof (ProofObj -> SBV Bool)
-> (Proof a -> ProofObj) -> Proof a -> SBV Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proof a -> ProofObj
forall a. Proof a -> ProofObj
proofOf
data ProofObj = ProofObj { ProofObj -> [ProofObj]
dependencies :: [ProofObj]
, ProofObj -> Bool
isUserAxiom :: Bool
, ProofObj -> SBV Bool
getObjProof :: SBool
, ProofObj -> Dynamic
getProp :: Dynamic
, ProofObj -> String
proofName :: String
, ProofObj -> TPUnique
uniqId :: TPUnique
, ProofObj -> Bool
isCached :: Bool
}
shortProofName :: ProofObj -> String
shortProofName :: ProofObj -> String
shortProofName ProofObj
p | String
" @ " String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
s = String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'@') (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
s
| Bool
True = String
s
where s :: String
s = ProofObj -> String
proofName ProofObj
p
newtype RootOfTrust = RootOfTrust (Maybe [ProofObj])
instance Show RootOfTrust where
show :: RootOfTrust -> String
show (RootOfTrust Maybe [ProofObj]
mbp) = case Maybe [ProofObj]
mbp of
Maybe [ProofObj]
Nothing -> String
"Nothing"
Just [ProofObj]
ps -> String
"Just [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ((ProofObj -> String) -> [ProofObj] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ProofObj -> String
shortProofName [ProofObj]
ps) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
instance Semigroup RootOfTrust where
RootOfTrust Maybe [ProofObj]
as <> :: RootOfTrust -> RootOfTrust -> RootOfTrust
<> RootOfTrust Maybe [ProofObj]
bs = Maybe [ProofObj] -> RootOfTrust
RootOfTrust (Maybe [ProofObj] -> RootOfTrust)
-> Maybe [ProofObj] -> RootOfTrust
forall a b. (a -> b) -> a -> b
$ (ProofObj -> ProofObj -> Bool) -> [ProofObj] -> [ProofObj]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy (\ProofObj
a ProofObj
b -> ProofObj -> TPUnique
uniqId ProofObj
a TPUnique -> TPUnique -> Bool
forall a. Eq a => a -> a -> Bool
== ProofObj -> TPUnique
uniqId ProofObj
b) ([ProofObj] -> [ProofObj]) -> Maybe [ProofObj] -> Maybe [ProofObj]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe [ProofObj]
as Maybe [ProofObj] -> Maybe [ProofObj] -> Maybe [ProofObj]
forall a. Semigroup a => a -> a -> a
<> Maybe [ProofObj]
bs)
instance Monoid RootOfTrust where
mempty :: RootOfTrust
mempty = Maybe [ProofObj] -> RootOfTrust
RootOfTrust Maybe [ProofObj]
forall a. Maybe a
Nothing
instance NFData ProofObj where
rnf :: ProofObj -> ()
rnf (ProofObj [ProofObj]
dependencies Bool
isUserAxiom SBV Bool
getObjProof Dynamic
_getProp String
proofName TPUnique
uniqId Bool
isCached) = [ProofObj] -> ()
forall a. NFData a => a -> ()
rnf [ProofObj]
dependencies
() -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
isUserAxiom
() -> () -> ()
forall a b. a -> b -> b
`seq` SBV Bool -> ()
forall a. NFData a => a -> ()
rnf SBV Bool
getObjProof
() -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
proofName
() -> () -> ()
forall a b. a -> b -> b
`seq` TPUnique -> ()
forall a. NFData a => a -> ()
rnf TPUnique
uniqId
() -> () -> ()
forall a b. a -> b -> b
`seq` Bool -> ()
forall a. NFData a => a -> ()
rnf Bool
isCached
data ProofTree = ProofTree ProofObj [ProofTree]
getProofTree :: ProofObj -> ProofTree
getProofTree :: ProofObj -> ProofTree
getProofTree ProofObj
p = ProofObj -> [ProofTree] -> ProofTree
ProofTree ProofObj
p ([ProofTree] -> ProofTree) -> [ProofTree] -> ProofTree
forall a b. (a -> b) -> a -> b
$ (ProofObj -> ProofTree) -> [ProofObj] -> [ProofTree]
forall a b. (a -> b) -> [a] -> [b]
map ProofObj -> ProofTree
getProofTree (ProofObj -> [ProofObj]
dependencies ProofObj
p)
depsToTree :: Bool -> [TPUnique] -> (String -> Int -> Int -> a) -> (Int, ProofTree) -> ([TPUnique], Tree a)
depsToTree :: forall a.
Bool
-> [TPUnique]
-> (String -> Int -> Int -> a)
-> (Int, ProofTree)
-> ([TPUnique], Tree a)
depsToTree Bool
shouldCompress [TPUnique]
visited String -> Int -> Int -> a
xform (Int
cnt, ProofTree ProofObj
top [ProofTree]
ds) = ([TPUnique]
nVisited, a -> [Tree a] -> Tree a
forall a. a -> [Tree a] -> Tree a
Node (String -> Int -> Int -> a
xform String
nTop Int
cnt ([Tree a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Tree a]
chlds)) [Tree a]
chlds)
where nTop :: String
nTop = ProofObj -> String
shortProofName ProofObj
top
uniq :: TPUnique
uniq = ProofObj -> TPUnique
uniqId ProofObj
top
([TPUnique]
nVisited, [Tree a]
chlds)
| Bool
shouldCompress Bool -> Bool -> Bool
&& TPUnique
uniq TPUnique -> [TPUnique] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TPUnique]
visited = ([TPUnique]
visited, [])
| Bool
shouldCompress = [TPUnique] -> [(Int, ProofTree)] -> ([TPUnique], [Tree a])
walk (TPUnique
uniq TPUnique -> [TPUnique] -> [TPUnique]
forall a. a -> [a] -> [a]
: [TPUnique]
visited) ([ProofTree] -> [(Int, ProofTree)]
compress ((ProofTree -> Bool) -> [ProofTree] -> [ProofTree]
forall a. (a -> Bool) -> [a] -> [a]
filter ProofTree -> Bool
interesting [ProofTree]
ds))
| Bool
True = [TPUnique] -> [(Int, ProofTree)] -> ([TPUnique], [Tree a])
walk [TPUnique]
visited ((ProofTree -> (Int, ProofTree))
-> [ProofTree] -> [(Int, ProofTree)]
forall a b. (a -> b) -> [a] -> [b]
map (Int
1,) ((ProofTree -> Bool) -> [ProofTree] -> [ProofTree]
forall a. (a -> Bool) -> [a] -> [a]
filter ProofTree -> Bool
interesting [ProofTree]
ds))
walk :: [TPUnique] -> [(Int, ProofTree)] -> ([TPUnique], [Tree a])
walk [TPUnique]
v [] = ([TPUnique]
v, [])
walk [TPUnique]
v ((Int, ProofTree)
c:[(Int, ProofTree)]
cs) = let ([TPUnique]
v', Tree a
t) = Bool
-> [TPUnique]
-> (String -> Int -> Int -> a)
-> (Int, ProofTree)
-> ([TPUnique], Tree a)
forall a.
Bool
-> [TPUnique]
-> (String -> Int -> Int -> a)
-> (Int, ProofTree)
-> ([TPUnique], Tree a)
depsToTree Bool
shouldCompress [TPUnique]
v String -> Int -> Int -> a
xform (Int, ProofTree)
c
([TPUnique]
v'', [Tree a]
ts) = [TPUnique] -> [(Int, ProofTree)] -> ([TPUnique], [Tree a])
walk [TPUnique]
v' [(Int, ProofTree)]
cs
in ([TPUnique]
v'', Tree a
t Tree a -> [Tree a] -> [Tree a]
forall a. a -> [a] -> [a]
: [Tree a]
ts)
interesting :: ProofTree -> Bool
interesting (ProofTree ProofObj
p [ProofTree]
_) = case ProofObj -> TPUnique
uniqId ProofObj
p of
TPUnique
TPInternal -> Bool
False
TPUnique
TPSorry -> Bool
True
TPUnique
TPQC -> Bool
True
TPUser{} -> Bool
True
compress :: [ProofTree] -> [(Int, ProofTree)]
compress :: [ProofTree] -> [(Int, ProofTree)]
compress [] = []
compress (ProofTree
p : [ProofTree]
ps) = (Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [()] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [() | (ProofTree
_, Bool
True) <- [(ProofTree, Bool)]
filtered], ProofTree
p) (Int, ProofTree) -> [(Int, ProofTree)] -> [(Int, ProofTree)]
forall a. a -> [a] -> [a]
: [ProofTree] -> [(Int, ProofTree)]
compress [ProofTree
d | (ProofTree
d, Bool
False) <- [(ProofTree, Bool)]
filtered]
where filtered :: [(ProofTree, Bool)]
filtered = [(ProofTree
d, ProofObj -> TPUnique
uniqId ProofObj
p' TPUnique -> TPUnique -> Bool
forall a. Eq a => a -> a -> Bool
== TPUnique
curUniq) | d :: ProofTree
d@(ProofTree ProofObj
p' [ProofTree]
_) <- [ProofTree]
ps]
curUniq :: TPUnique
curUniq = case ProofTree
p of
ProofTree ProofObj
curProof [ProofTree]
_ -> ProofObj -> TPUnique
uniqId ProofObj
curProof
showProofTree :: Bool -> Proof a -> String
showProofTree :: forall a. Bool -> Proof a -> String
showProofTree Bool
compress Proof a
d = Tree String -> String
showTree (Tree String -> String) -> Tree String -> String
forall a b. (a -> b) -> a -> b
$ ([TPUnique], Tree String) -> Tree String
forall a b. (a, b) -> b
snd (([TPUnique], Tree String) -> Tree String)
-> ([TPUnique], Tree String) -> Tree String
forall a b. (a -> b) -> a -> b
$ Bool
-> [TPUnique]
-> (String -> Int -> Int -> String)
-> (Int, ProofTree)
-> ([TPUnique], Tree String)
forall a.
Bool
-> [TPUnique]
-> (String -> Int -> Int -> a)
-> (Int, ProofTree)
-> ([TPUnique], Tree a)
depsToTree Bool
compress [] String -> Int -> Int -> String
forall {a} {p}. (Eq a, Num a, Show a) => String -> a -> p -> String
sh (Int
1, ProofObj -> ProofTree
getProofTree (Proof a -> ProofObj
forall a. Proof a -> ProofObj
proofOf Proof a
d))
where sh :: String -> a -> p -> String
sh String
nm a
1 p
_ = String
nm
sh String
nm a
x p
_= String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (x" String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
showProofTreeHTML :: Bool -> Maybe FilePath -> Proof a -> String
showProofTreeHTML :: forall a. Bool -> Maybe String -> Proof a -> String
showProofTreeHTML Bool
compress Maybe String
mbCSS Proof a
p = Maybe String -> Tree NodeInfo -> String
htmlTree Maybe String
mbCSS (Tree NodeInfo -> String) -> Tree NodeInfo -> String
forall a b. (a -> b) -> a -> b
$ ([TPUnique], Tree NodeInfo) -> Tree NodeInfo
forall a b. (a, b) -> b
snd (([TPUnique], Tree NodeInfo) -> Tree NodeInfo)
-> ([TPUnique], Tree NodeInfo) -> Tree NodeInfo
forall a b. (a -> b) -> a -> b
$ Bool
-> [TPUnique]
-> (String -> Int -> Int -> NodeInfo)
-> (Int, ProofTree)
-> ([TPUnique], Tree NodeInfo)
forall a.
Bool
-> [TPUnique]
-> (String -> Int -> Int -> a)
-> (Int, ProofTree)
-> ([TPUnique], Tree a)
depsToTree Bool
compress [] String -> Int -> Int -> NodeInfo
nodify (Int
1, ProofObj -> ProofTree
getProofTree (Proof a -> ProofObj
forall a. Proof a -> ProofObj
proofOf Proof a
p))
where nodify :: String -> Int -> Int -> NodeInfo
nodify :: String -> Int -> Int -> NodeInfo
nodify String
nm Int
cnt Int
dc = NodeInfo { nodeBehavior :: Behavior
nodeBehavior = Behavior
InitiallyExpanded
, nodeName :: String
nodeName = String
nm
, nodeInfo :: String
nodeInfo = String -> String
spc (Int -> String
forall {a}. (Eq a, Num a, Show a) => a -> String
used Int
cnt) String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall {a}. (Eq a, Num a, Show a) => a -> String
depCount Int
dc
}
used :: a -> String
used a
1 = String
""
used a
n = String
"Used " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" times."
spc :: String -> String
spc String
"" = String
""
spc String
s = String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" "
depCount :: a -> String
depCount a
0 = String
""
depCount a
1 = String
"Has one dependency."
depCount a
n = String
"Has " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" dependencies."
instance Typeable a => Show (Proof a) where
show :: Proof a -> String
show p :: Proof a
p@(Proof po :: ProofObj
po@ProofObj{proofName :: ProofObj -> String
proofName = String
nm}) = Char
'[' Char -> String -> String
forall a. a -> [a] -> [a]
: RootOfTrust -> String
sh (Proof a -> RootOfTrust
forall a. Proof a -> RootOfTrust
rootOfTrust Proof a
p) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"] " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" :: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
pretty (TypeRep -> String
forall a. Show a => a -> String
show (Proof a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf Proof a
p))
where sh :: RootOfTrust -> String
sh (RootOfTrust Maybe [ProofObj]
Nothing) = String
"Proven" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
cacheInfo
sh (RootOfTrust (Just [ProofObj]
ps)) = String
"Modulo: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [ProofObj] -> String
join [ProofObj]
ps String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
cacheInfo
join :: [ProofObj] -> String
join = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ([String] -> String)
-> ([ProofObj] -> [String]) -> [ProofObj] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String])
-> ([ProofObj] -> [String]) -> [ProofObj] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProofObj -> String) -> [ProofObj] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ProofObj -> String
shortProofName
cacheInfo :: String
cacheInfo = case ProofObj -> [ProofObj]
cachedProofs ProofObj
po of
[] -> String
""
[ProofObj]
cs -> String
". Cached: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [ProofObj] -> String
join ((ProofObj -> ProofObj -> Bool) -> [ProofObj] -> [ProofObj]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy (\ProofObj
p1 ProofObj
p2 -> ProofObj -> TPUnique
uniqId ProofObj
p1 TPUnique -> TPUnique -> Bool
forall a. Eq a => a -> a -> Bool
== ProofObj -> TPUnique
uniqId ProofObj
p2) [ProofObj]
cs)
cachedProofs :: ProofObj -> [ProofObj]
cachedProofs prf :: ProofObj
prf@ProofObj{Bool
isCached :: ProofObj -> Bool
isCached :: Bool
isCached} = if Bool
isCached then ProofObj
prf ProofObj -> [ProofObj] -> [ProofObj]
forall a. a -> [a] -> [a]
: [ProofObj]
rest else [ProofObj]
rest
where rest :: [ProofObj]
rest = (ProofObj -> [ProofObj]) -> [ProofObj] -> [ProofObj]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ProofObj -> [ProofObj]
cachedProofs (ProofObj -> [ProofObj]
dependencies ProofObj
prf)
pretty :: String -> String
pretty :: String -> String
pretty = [String] -> String
unwords ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
walk ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> [String]) -> (String -> String) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> String) -> String -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',' then String
" , " else [Char
c]) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
clean
where fa :: String -> [String]
fa String
v = [Char
'Ɐ' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
unQuote String
v, String
"∷"]
ex :: String -> [String]
ex String
v = [Char
'∃' Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
unQuote String
v, String
"∷"]
walk :: [String] -> [String]
walk (String
"SBV" : String
"Bool" : [String]
rest) = [String] -> [String]
walk ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
"Bool" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
rest
walk (String
"Forall" : String
xs : [String]
rest) = [String] -> [String]
walk ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
fa String
xs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
rest
walk (String
"Exists" : String
xs : [String]
rest) = [String] -> [String]
walk ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String -> [String]
ex String
xs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
rest
walk (String
"->" : [String]
rest) = [String] -> [String]
walk ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ String
"→" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
rest
walk (String
"((Forall" : String
xs : String
t1 : String
"," : String
"(Forall" : String
ys : String
t2 : [String]
rest) = [String] -> [String]
ap (String -> [String]
fa String
xs) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String -> String
np String
t1 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
","] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
fa String
ys [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String -> String
np String
t2] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String] -> [String]
walk [String]
rest
where
np :: String -> String
np String
s | String
")" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
s = String -> String
forall a. HasCallStack => [a] -> [a]
init String
s
| Bool
True = String
s
ap :: [String] -> [String]
ap (String
t : [String]
ts) = (Char
'('Char -> String -> String
forall a. a -> [a] -> [a]
:String
t) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
ts
ap [] = []
walk (String
c : [String]
cs) = String
c String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String] -> [String]
walk [String]
cs
walk [] = []
clean :: String -> String
clean :: String -> String
clean String
s | String
pre String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
s Bool -> Bool -> Bool
&& String
suf String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
s
= String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
drop (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
suf) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
drop (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
pre) (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
s
| Bool
True
= String
s
where pre :: String
pre = String
"Proof ("
suf :: String
suf = String
")"
sorry :: ProofObj
sorry :: ProofObj
sorry = ProofObj { dependencies :: [ProofObj]
dependencies = []
, isUserAxiom :: Bool
isUserAxiom = Bool
False
, getObjProof :: SBV Bool
getObjProof = String -> SBV Bool -> SBV Bool
forall a. SymVal a => String -> SBV a -> SBV a
label String
"sorry" ((Forall "__sbvTP_sorry" Bool -> SBV Bool) -> SBV Bool
forall a. QuantifiedBool a => a -> SBV Bool
quantifiedBool Forall "__sbvTP_sorry" Bool -> SBV Bool
p)
, getProp :: Dynamic
getProp = (Forall "__sbvTP_sorry" Bool -> SBV Bool) -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn Forall "__sbvTP_sorry" Bool -> SBV Bool
p
, proofName :: String
proofName = String
"sorry"
, uniqId :: TPUnique
uniqId = TPUnique
TPSorry
, isCached :: Bool
isCached = Bool
False
}
where
p :: Forall "__sbvTP_sorry" Bool -> SBV Bool
p (Forall @"__sbvTP_sorry" (SBV Bool
x :: SBool)) = String -> SBV Bool -> SBV Bool
forall a. SymVal a => String -> SBV a -> SBV a
label String
"SORRY: TP, proof uses \"sorry\"" SBV Bool
x
quickCheckProof :: ProofObj
quickCheckProof :: ProofObj
quickCheckProof = ProofObj { dependencies :: [ProofObj]
dependencies = []
, isUserAxiom :: Bool
isUserAxiom = Bool
False
, getObjProof :: SBV Bool
getObjProof = String -> SBV Bool -> SBV Bool
forall a. SymVal a => String -> SBV a -> SBV a
label String
"quickCheck" ((Forall "__sbvTP_quickCheck" Bool -> SBV Bool) -> SBV Bool
forall a. QuantifiedBool a => a -> SBV Bool
quantifiedBool Forall "__sbvTP_quickCheck" Bool -> SBV Bool
p)
, getProp :: Dynamic
getProp = (Forall "__sbvTP_quickCheck" Bool -> SBV Bool) -> Dynamic
forall a. Typeable a => a -> Dynamic
toDyn Forall "__sbvTP_quickCheck" Bool -> SBV Bool
p
, proofName :: String
proofName = String
"quickCheck"
, uniqId :: TPUnique
uniqId = TPUnique
TPQC
, isCached :: Bool
isCached = Bool
False
}
where
p :: Forall "__sbvTP_quickCheck" Bool -> SBV Bool
p (Forall @"__sbvTP_quickCheck" (SBV Bool
x :: SBool)) = String -> SBV Bool -> SBV Bool
forall a. SymVal a => String -> SBV a -> SBV a
label String
"QUICKCHECK: TP, proof uses \"qc\"" SBV Bool
x
rootOfTrust :: Proof a -> RootOfTrust
rootOfTrust :: forall a. Proof a -> RootOfTrust
rootOfTrust = Bool -> ProofObj -> RootOfTrust
rot Bool
True (ProofObj -> RootOfTrust)
-> (Proof a -> ProofObj) -> Proof a -> RootOfTrust
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proof a -> ProofObj
forall a. Proof a -> ProofObj
proofOf
where rot :: Bool -> ProofObj -> RootOfTrust
rot Bool
atTop p :: ProofObj
p@ProofObj{uniqId :: ProofObj -> TPUnique
uniqId = TPUnique
curUniq, [ProofObj]
dependencies :: ProofObj -> [ProofObj]
dependencies :: [ProofObj]
dependencies} = RootOfTrust -> RootOfTrust
compress RootOfTrust
res
where res :: RootOfTrust
res = case TPUnique
curUniq of
TPUnique
TPInternal -> Maybe [ProofObj] -> RootOfTrust
RootOfTrust Maybe [ProofObj]
forall a. Maybe a
Nothing
TPUnique
TPQC -> Maybe [ProofObj] -> RootOfTrust
RootOfTrust (Maybe [ProofObj] -> RootOfTrust)
-> Maybe [ProofObj] -> RootOfTrust
forall a b. (a -> b) -> a -> b
$ [ProofObj] -> Maybe [ProofObj]
forall a. a -> Maybe a
Just [ProofObj
quickCheckProof]
TPUnique
TPSorry -> Maybe [ProofObj] -> RootOfTrust
RootOfTrust (Maybe [ProofObj] -> RootOfTrust)
-> Maybe [ProofObj] -> RootOfTrust
forall a b. (a -> b) -> a -> b
$ [ProofObj] -> Maybe [ProofObj]
forall a. a -> Maybe a
Just [ProofObj
sorry]
TPUser {} -> RootOfTrust
self RootOfTrust -> RootOfTrust -> RootOfTrust
forall a. Semigroup a => a -> a -> a
<> (ProofObj -> RootOfTrust) -> [ProofObj] -> RootOfTrust
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Bool -> ProofObj -> RootOfTrust
rot Bool
False) [ProofObj]
dependencies
self :: RootOfTrust
self | Bool
atTop = RootOfTrust
forall a. Monoid a => a
mempty
| (ProofObj -> Bool) -> [ProofObj] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ProofObj -> Bool
isUnsafe [ProofObj]
dependencies = Maybe [ProofObj] -> RootOfTrust
RootOfTrust (Maybe [ProofObj] -> RootOfTrust)
-> Maybe [ProofObj] -> RootOfTrust
forall a b. (a -> b) -> a -> b
$ [ProofObj] -> Maybe [ProofObj]
forall a. a -> Maybe a
Just [ProofObj
p]
| Bool
True = RootOfTrust
forall a. Monoid a => a
mempty
isUnsafe :: ProofObj -> Bool
isUnsafe ProofObj{uniqId :: ProofObj -> TPUnique
uniqId = TPUnique
u} = TPUnique
u TPUnique -> [TPUnique] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TPUnique
TPSorry, TPUnique
TPQC]
compress :: RootOfTrust -> RootOfTrust
compress (RootOfTrust Maybe [ProofObj]
mbps) = Maybe [ProofObj] -> RootOfTrust
RootOfTrust (Maybe [ProofObj] -> RootOfTrust)
-> Maybe [ProofObj] -> RootOfTrust
forall a b. (a -> b) -> a -> b
$ [ProofObj] -> [ProofObj]
reduce ([ProofObj] -> [ProofObj]) -> Maybe [ProofObj] -> Maybe [ProofObj]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [ProofObj]
mbps
where reduce :: [ProofObj] -> [ProofObj]
reduce [ProofObj]
ps = case (ProofObj -> Bool) -> [ProofObj] -> ([ProofObj], [ProofObj])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ProofObj -> Bool
isUnsafe [ProofObj]
ps of
([ProofObj]
l, []) | TPUnique
TPSorry TPUnique -> [TPUnique] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (ProofObj -> TPUnique) -> [ProofObj] -> [TPUnique]
forall a b. (a -> b) -> [a] -> [b]
map ProofObj -> TPUnique
uniqId [ProofObj]
l -> [ProofObj
sorry]
| Bool
True -> [ProofObj
quickCheckProof]
([ProofObj]
_, [ProofObj]
os) -> [ProofObj]
os
concludeModulo :: [ProofObj] -> String
concludeModulo :: [ProofObj] -> String
concludeModulo [ProofObj]
by = case (ProofObj -> RootOfTrust) -> [ProofObj] -> RootOfTrust
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Proof Any -> RootOfTrust
forall a. Proof a -> RootOfTrust
rootOfTrust (Proof Any -> RootOfTrust)
-> (ProofObj -> Proof Any) -> ProofObj -> RootOfTrust
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProofObj -> Proof Any
forall a. ProofObj -> Proof a
Proof) [ProofObj]
by of
RootOfTrust Maybe [ProofObj]
Nothing -> String
""
RootOfTrust (Just [ProofObj]
ps) -> String
" [Modulo: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ((ProofObj -> String) -> [ProofObj] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ProofObj -> String
shortProofName [ProofObj]
ps) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"
tpQuiet :: Bool -> SMTConfig -> SMTConfig
tpQuiet :: Bool -> SMTConfig -> SMTConfig
tpQuiet Bool
b SMTConfig
cfg = SMTConfig
cfg{tpOptions = (tpOptions cfg) { quiet = b }}
tpRibbon :: Int -> SMTConfig -> SMTConfig
tpRibbon :: Int -> SMTConfig -> SMTConfig
tpRibbon Int
i SMTConfig
cfg = SMTConfig
cfg{tpOptions = (tpOptions cfg) { ribbonLength = i }}
tpStats :: SMTConfig -> SMTConfig
tpStats :: SMTConfig -> SMTConfig
tpStats SMTConfig
cfg = SMTConfig
cfg{tpOptions = (tpOptions cfg) { printStats = True }}
tpCache :: SMTConfig -> SMTConfig
tpCache :: SMTConfig -> SMTConfig
tpCache SMTConfig
cfg = SMTConfig
cfg{tpOptions = (tpOptions cfg) { cacheProofs = True }}