{-# LANGUAGE NamedFieldPuns #-}
{-# OPTIONS_GHC -Wall -Werror #-}
module Data.SBV.SMT.Utils (
SMTLibConverter
, SMTLibIncConverter
, addAnnotations
, showTimeoutValue
, alignDiagnostic
, alignPlain
, debug
, mergeSExpr
, SBVException(..)
)
where
import qualified Control.Exception as C
import Control.Monad.Trans (MonadIO, liftIO)
import Data.SBV.Core.Data
import Data.SBV.Core.Symbolic (QueryContext, CnstMap)
import Data.SBV.Utils.Lib (joinArgs)
import Data.List (intercalate)
import qualified Data.Set as Set (Set)
import qualified Data.Sequence as S (Seq)
import System.Exit (ExitCode(..))
type SMTLibConverter a = QueryContext
-> Set.Set Kind
-> Bool
-> [String]
-> ([(Quantifier, NamedSymVar)], [NamedSymVar])
-> [Either SV (SV, [SV])]
-> (CnstMap, [(SV, CV)])
-> [((Int, Kind, Kind), [SV])]
-> [(Int, ArrayInfo)]
-> [(String, SBVType)]
-> [(Bool, String, [String])]
-> SBVPgm
-> S.Seq (Bool, [(String, String)], SV)
-> SV
-> SMTConfig
-> a
type SMTLibIncConverter a = [NamedSymVar]
-> Set.Set Kind
-> (CnstMap, [(SV, CV)])
-> [(Int, ArrayInfo)]
-> [((Int, Kind, Kind), [SV])]
-> [(String, SBVType)]
-> SBVPgm
-> S.Seq (Bool, [(String, String)], SV)
-> SMTConfig
-> a
addAnnotations :: [(String, String)] -> String -> String
addAnnotations :: [(String, String)] -> String -> String
addAnnotations [] String
x = String
x
addAnnotations [(String, String)]
atts String
x = String
"(! " forall a. [a] -> [a] -> [a]
++ String
x forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords (forall a b. (a -> b) -> [a] -> [b]
map forall {t :: * -> *}. Foldable t => (String, t Char) -> String
mkAttr [(String, String)]
atts) forall a. [a] -> [a] -> [a]
++ String
")"
where mkAttr :: (String, t Char) -> String
mkAttr (String
a, t Char
v) = String
a forall a. [a] -> [a] -> [a]
++ String
" |" forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Char -> String
sanitize t Char
v forall a. [a] -> [a] -> [a]
++ String
"|"
sanitize :: Char -> String
sanitize Char
'|' = String
"_bar_"
sanitize Char
'\\' = String
"_backslash_"
sanitize Char
c = [Char
c]
showTimeoutValue :: Int -> String
showTimeoutValue :: Int -> String
showTimeoutValue Int
i = case (Int
i forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
1000000, Int
i forall a. Integral a => a -> a -> (a, a)
`quotRem` Int
500000) of
((Int
s, Int
0), (Int, Int)
_) -> forall a. Show a => a -> String -> String
shows Int
s String
"s"
((Int, Int)
_, (Int
hs, Int
0)) -> forall a. Show a => a -> String -> String
shows (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
hs forall a. Fractional a => a -> a -> a
/ (Float
2::Float)) String
"s"
((Int, Int), (Int, Int))
_ -> forall a. Show a => a -> String -> String
shows Int
i String
"ms"
alignDiagnostic :: String -> String -> String
alignDiagnostic :: String -> String -> String
alignDiagnostic = String -> String -> String -> String
alignWithPrefix String
"*** "
alignPlain :: String -> String -> String
alignPlain :: String -> String -> String
alignPlain = String -> String -> String -> String
alignWithPrefix String
""
alignWithPrefix :: String -> String -> String -> String
alignWithPrefix :: String -> String -> String -> String
alignWithPrefix String
pre String
tag String
multi = forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. [a] -> [a] -> [a]
(++) (String
tag forall a. a -> [a] -> [a]
: forall a. a -> [a]
repeat (String
pre forall a. [a] -> [a] -> [a]
++ forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
tag forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. Foldable t => t a -> Int
length String
pre) Char
' ')) (forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) (String -> [String]
lines String
multi))
debug :: MonadIO m => SMTConfig -> [String] -> m ()
debug :: forall (m :: * -> *). MonadIO m => SMTConfig -> [String] -> m ()
debug SMTConfig
cfg
| Bool -> Bool
not (SMTConfig -> Bool
verbose SMTConfig
cfg) = forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())
| Just String
f <- SMTConfig -> Maybe String
redirectVerbose SMTConfig
cfg = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String -> String -> IO ()
appendFile String
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. [a] -> [a] -> [a]
++ String
"\n"))
| Bool
True = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
putStrLn
mergeSExpr :: [String] -> [String]
mergeSExpr :: [String] -> [String]
mergeSExpr [] = []
mergeSExpr (String
x:[String]
xs)
| Int
d forall a. Eq a => a -> a -> Bool
== Int
0 = String
x forall a. a -> [a] -> [a]
: [String] -> [String]
mergeSExpr [String]
xs
| Bool
True = let ([String]
f, [String]
r) = Int -> [String] -> ([String], [String])
grab Int
d [String]
xs in [String] -> String
unlines (String
xforall a. a -> [a] -> [a]
:[String]
f) forall a. a -> [a] -> [a]
: [String] -> [String]
mergeSExpr [String]
r
where d :: Int
d = String -> Int
parenDiff String
x
parenDiff :: String -> Int
parenDiff :: String -> Int
parenDiff = forall {a}. Num a => a -> String -> a
go Int
0
where go :: a -> String -> a
go a
i String
"" = a
i
go a
i (Char
'(':String
cs) = let i' :: a
i'= a
iforall a. Num a => a -> a -> a
+a
1 in a
i' seq :: forall a b. a -> b -> b
`seq` a -> String -> a
go a
i' String
cs
go a
i (Char
')':String
cs) = let i' :: a
i'= a
iforall a. Num a => a -> a -> a
-a
1 in a
i' seq :: forall a b. a -> b -> b
`seq` a -> String -> a
go a
i' String
cs
go a
i (Char
'"':String
cs) = a -> String -> a
go a
i (String -> String
skipString String
cs)
go a
i (Char
'|':String
cs) = a -> String -> a
go a
i (String -> String
skipBar String
cs)
go a
i (Char
_ :String
cs) = a -> String -> a
go a
i String
cs
grab :: Int -> [String] -> ([String], [String])
grab Int
i [String]
ls
| Int
i forall a. Ord a => a -> a -> Bool
<= Int
0 = ([], [String]
ls)
grab Int
_ [] = ([], [])
grab Int
i (String
l:[String]
ls) = let ([String]
a, [String]
b) = Int -> [String] -> ([String], [String])
grab (Int
iforall a. Num a => a -> a -> a
+String -> Int
parenDiff String
l) [String]
ls in (String
lforall a. a -> [a] -> [a]
:[String]
a, [String]
b)
skipString :: String -> String
skipString (Char
'"':Char
'"':String
cs) = String -> String
skipString String
cs
skipString (Char
'"':String
cs) = String
cs
skipString (Char
_:String
cs) = String -> String
skipString String
cs
skipString [] = []
skipBar :: String -> String
skipBar (Char
'|':String
cs) = String
cs
skipBar (Char
_:String
cs) = String -> String
skipBar String
cs
skipBar [] = []
data SBVException = SBVException {
SBVException -> String
sbvExceptionDescription :: String
, SBVException -> Maybe String
sbvExceptionSent :: Maybe String
, SBVException -> Maybe String
sbvExceptionExpected :: Maybe String
, SBVException -> Maybe String
sbvExceptionReceived :: Maybe String
, SBVException -> Maybe String
sbvExceptionStdOut :: Maybe String
, SBVException -> Maybe String
sbvExceptionStdErr :: Maybe String
, SBVException -> Maybe ExitCode
sbvExceptionExitCode :: Maybe ExitCode
, SBVException -> SMTConfig
sbvExceptionConfig :: SMTConfig
, SBVException -> Maybe [String]
sbvExceptionReason :: Maybe [String]
, SBVException -> Maybe [String]
sbvExceptionHint :: Maybe [String]
}
instance C.Exception SBVException
instance Show SBVException where
show :: SBVException -> String
show SBVException { String
sbvExceptionDescription :: String
sbvExceptionDescription :: SBVException -> String
sbvExceptionDescription
, Maybe String
sbvExceptionSent :: Maybe String
sbvExceptionSent :: SBVException -> Maybe String
sbvExceptionSent
, Maybe String
sbvExceptionExpected :: Maybe String
sbvExceptionExpected :: SBVException -> Maybe String
sbvExceptionExpected
, Maybe String
sbvExceptionReceived :: Maybe String
sbvExceptionReceived :: SBVException -> Maybe String
sbvExceptionReceived
, Maybe String
sbvExceptionStdOut :: Maybe String
sbvExceptionStdOut :: SBVException -> Maybe String
sbvExceptionStdOut
, Maybe String
sbvExceptionStdErr :: Maybe String
sbvExceptionStdErr :: SBVException -> Maybe String
sbvExceptionStdErr
, Maybe ExitCode
sbvExceptionExitCode :: Maybe ExitCode
sbvExceptionExitCode :: SBVException -> Maybe ExitCode
sbvExceptionExitCode
, SMTConfig
sbvExceptionConfig :: SMTConfig
sbvExceptionConfig :: SBVException -> SMTConfig
sbvExceptionConfig
, Maybe [String]
sbvExceptionReason :: Maybe [String]
sbvExceptionReason :: SBVException -> Maybe [String]
sbvExceptionReason
, Maybe [String]
sbvExceptionHint :: Maybe [String]
sbvExceptionHint :: SBVException -> Maybe [String]
sbvExceptionHint
}
= let grp1 :: [String]
grp1 = [ String
""
, String
"*** Data.SBV: " forall a. [a] -> [a] -> [a]
++ String
sbvExceptionDescription forall a. [a] -> [a] -> [a]
++ String
":"
]
grp2 :: [String]
grp2 = [String
"*** Sent : " String -> String -> String
`alignDiagnostic` String
snt | Just String
snt <- [Maybe String
sbvExceptionSent], Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
snt ]
forall a. [a] -> [a] -> [a]
++ [String
"*** Expected : " String -> String -> String
`alignDiagnostic` String
excp | Just String
excp <- [Maybe String
sbvExceptionExpected], Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
excp]
forall a. [a] -> [a] -> [a]
++ [String
"*** Received : " String -> String -> String
`alignDiagnostic` String
rcvd | Just String
rcvd <- [Maybe String
sbvExceptionReceived], Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
rcvd]
grp3 :: [String]
grp3 = [String
"*** Stdout : " String -> String -> String
`alignDiagnostic` String
out | Just String
out <- [Maybe String
sbvExceptionStdOut], Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
out ]
forall a. [a] -> [a] -> [a]
++ [String
"*** Stderr : " String -> String -> String
`alignDiagnostic` String
err | Just String
err <- [Maybe String
sbvExceptionStdErr], Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
err ]
forall a. [a] -> [a] -> [a]
++ [String
"*** Exit code : " String -> String -> String
`alignDiagnostic` forall a. Show a => a -> String
show ExitCode
ec | Just ExitCode
ec <- [Maybe ExitCode
sbvExceptionExitCode] ]
forall a. [a] -> [a] -> [a]
++ [String
"*** Executable: " String -> String -> String
`alignDiagnostic` SMTSolver -> String
executable (SMTConfig -> SMTSolver
solver SMTConfig
sbvExceptionConfig) ]
forall a. [a] -> [a] -> [a]
++ [String
"*** Options : " String -> String -> String
`alignDiagnostic` [String] -> String
joinArgs (SMTSolver -> SMTConfig -> [String]
options (SMTConfig -> SMTSolver
solver SMTConfig
sbvExceptionConfig) SMTConfig
sbvExceptionConfig) ]
grp4 :: [String]
grp4 = [String
"*** Reason : " String -> String -> String
`alignDiagnostic` [String] -> String
unlines [String]
rsn | Just [String]
rsn <- [Maybe [String]
sbvExceptionReason]]
forall a. [a] -> [a] -> [a]
++ [String
"*** Hint : " String -> String -> String
`alignDiagnostic` [String] -> String
unlines [String]
hnt | Just [String]
hnt <- [Maybe [String]
sbvExceptionHint ]]
join :: [[String]] -> [String]
join [] = []
join [[String]
x] = [String]
x
join ([String]
g:[[String]]
gs) = case [[String]] -> [String]
join [[String]]
gs of
[] -> [String]
g
[String]
rest -> [String]
g forall a. [a] -> [a] -> [a]
++ [String
"***"] forall a. [a] -> [a] -> [a]
++ [String]
rest
in [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ [[String]] -> [String]
join [[String]
grp1, [String]
grp2, [String]
grp3, [String]
grp4]