module System.Isabelle (
checkTheoryFile
) where
import Data.Maybe
import Data.List
import System.FilePath
import System.Directory
import System.Process
import System.IO
import Control.Concurrent
import Control.Monad
import Control.Exception
withTempFile :: FilePath -> String -> ((FilePath, Handle) -> IO a) -> IO (a, FilePath)
withTempFile dir nameTemplate io =
bracket (openTempFile dir nameTemplate) (hClose . snd)
(\args@(file,_) -> do{ x <- io args; return (x, file) })
withTempFile_ :: FilePath -> String -> ((FilePath, Handle) -> IO a) -> IO FilePath
withTempFile_ dir nameTemplate io = snd `liftM` withTempFile dir nameTemplate io
waitForProcessTimeout :: Int -> ProcessHandle -> IO Bool
waitForProcessTimeout maxTime hProc
| maxTime <= 0 = do _<- waitForProcess hProc; return False
| otherwise = do
timeout <- newMVar False
_ <- forkIO $ do
threadDelay maxTime
modifyMVar_ timeout (return . const True)
terminateProcess hProc
_ <- waitForProcess hProc
readMVar timeout
checkTheoryFile :: FilePath
-> Maybe Int
-> Int
-> String
-> FilePath
-> IO (IO String, Maybe String)
checkTheoryFile isabelleTool threads maxTime logic thyFile = do
let thyName = takeBaseName thyFile
rootName = "ROOT-" ++ thyName ++ ".ML"
sessionName = "scyther-proof-" ++ thyName
tmpDir <- getTemporaryDirectory
rootFile <- withTempFile_ tmpDir rootName
(\(_, hRootFile) ->
hPutStrLn hRootFile $ "use_thy \"" ++ dropExtension thyFile ++ "\""
)
finally
(do let cmd = isabelleTool ++
" usedir -f " ++ rootFile ++
" -s " ++ sessionName ++
" -M " ++ maybe "0" show threads ++
" " ++ logic ++ " ."
(_, _, hErr, hProc) <- runInteractiveCommand cmd
isaOutVar <- newEmptyMVar
_ <-forkIO $ redirect hErr isaOutVar
timeout <- waitForProcessTimeout maxTime hProc
isaOut <- takeMVar isaOutVar
if timeout
then do return (return $ isaOut ++ "Interrupted due to timeout!"
, Just $ "timeout: " ++
show ((fromIntegral maxTime / 10E6)::Double) ++ "s")
else do return $ parseIsaOutput sessionName isaOut
)
(do removeFile rootFile)
where
redirect hIn mvar = hGetContents hIn >>= putMVar mvar
logFileName str = fromMaybe "no log file" $ do
let logIndicator = "(see also "
line <- find (logIndicator `isPrefixOf`) (lines str)
init `liftM` stripPrefix logIndicator line
errMsg str = case break ("***" `isPrefixOf`) (lines str) of
(_,[]) -> str
(_,first:ls) -> case break ("***" `isPrefixOf`) ls of
(_,[]) -> unlines (first : ls)
(ls',(fin:_)) -> unlines (first : ls'++[fin])
parseIsaOutput sessionName str
| ("Finished "++logic++"-"++sessionName) `isInfixOf` str = (return str, Nothing)
| otherwise = (readFile (logFileName str), Just (errMsg str))