5923N/ADescription : Interface to the TPTP theorem prover via Darwin.
5923N/ACopyright : (c) Heng Jiang, Uni Bremen 2004-2007
5923N/AMaintainer : jiang@informatik.uni-bremen.de
-- preliminary hacks for display of CASL models
-- * Prover implementation
data ProverBinary = Darwin | EDarwin
proverBinary :: ProverBinary -> String
proverBinary b = case b of
{- | The Prover implementation. First runs the batch prover (with
graphical feedback), then starts the GUI prover. -}
:: ProverBinary -> Prover Sign Sentence SoftFOLMorphism () ProofTree
darwinProver b = mkAutomaticProver (proverBinary b) () (darwinGUI b)
$ darwinCMDLautomaticBatchAux b
:: ProverBinary -> ConsChecker Sign Sentence () SoftFOLMorphism ProofTree
darwinConsChecker b = (mkConsChecker (proverBinary b) () $ consCheck b)
Record for prover specific functions. This is used by both GUI and command
atpFun :: ProverBinary -- ^ the actual binary
-> String -- ^ theory name
-> ATPFunctions Sign Sentence SoftFOLMorphism ProofTree SoftFOLProverState
atpFun b thName = ATPFunctions
{ initialProverState = spassProverState
, atpTransSenName = transSenName
, atpInsertSentence = insertSentenceGen
, goalOutput = showTPTPProblem thName
, proverHelpText = "no help for darwin available"
, batchTimeEnv = "HETS_SPASS_BATCH_TIME_LIMIT"
, fileExtensions = FileExtensions
{ problemOutput = ".tptp"
, proverOutput = ".spass"
, theoryConfiguration = ".spcf" }
, runProver = runDarwin b
, createProverOptions = extraOpts }
Invokes the generic prover GUI. SPASS specific functions are omitted by
:: ProverBinary -- ^ the actual binary
-> String -- ^ theory name
-> Theory Sign Sentence ProofTree
-- ^ theory consisting of a signature and sentences
-> [FreeDefMorphism SPTerm SoftFOLMorphism] -- ^ freeness constraints
-> IO [ProofStatus ProofTree] -- ^ proof status for each goal
darwinGUI b thName th freedefs =
genericATPgui (atpFun b thName) True (proverBinary b) thName th
-- ** command line function
automatic command line interface to the Darwin prover.
Darwin specific functions are omitted by data type ATPFunctions.
:: Bool -- ^ True means include proved theorems
-> Bool -- ^ True means save problem file
-- ^ used to store the result of the batch run
-> String -- ^ theory name
-> TacticScript -- ^ default tactic script
-> Theory Sign Sentence ProofTree
-- ^ theory consisting of a signature and sentences
-> [FreeDefMorphism SPTerm SoftFOLMorphism] -- ^ freeness constraints
-- ^ fst: identifier of the batch thread for killing it
-- snd: MVar to wait for the end of the thread
darwinCMDLautomaticBatch = darwinCMDLautomaticBatchAux Darwin
darwinCMDLautomaticBatchAux
:: ProverBinary -- ^ the actual binary
-> Bool -- ^ True means include proved theorems
-> Bool -- ^ True means save problem file
-- ^ used to store the result of the batch run
-> String -- ^ theory name
-> TacticScript -- ^ default tactic script
-> Theory Sign Sentence ProofTree
-- ^ theory consisting of a signature and sentences
-> [FreeDefMorphism SPTerm SoftFOLMorphism] -- ^ freeness constraints
-- ^ fst: identifier of the batch thread for killing it
-- snd: MVar to wait for the end of the thread
darwinCMDLautomaticBatchAux b inclProvedThs saveProblem_batch resultMVar
thName defTS th freedefs =
genericCMDLautomaticBatch (atpFun b thName) inclProvedThs saveProblem_batch
resultMVar (proverBinary b) thName
(parseTacticScript batchTimeLimit [] defTS) th freedefs emptyProofTree
-- * Main prover functions
Runs the Darwin service. The tactic script only contains a string for the
-> TheoryMorphism Sign Sentence SoftFOLMorphism ProofTree
-> [FreeDefMorphism SPTerm SoftFOLMorphism] -- ^ freeness constraints
-> IO (CCStatus ProofTree)
consCheck b thName (TacticScript tl) tm freedefs = case tTarget tm of
let proverStateI = spassProverState sig (toNamedList nSens) freedefs
extraOptions = "-pc false -pmtptp true -fd true -to " ++ tl
prob <- showTPTPProblemM thName proverStateI []
(exitCode, out, tUsed) <-
runDarwinProcess bin False extraOptions thName prob
, ccProofTree = ProofTree $ unlines $ exitCode : out
, ccUsedTime = timeToTimeOfDay $ secondsToDiffTime
return $ if szsProved exitCode then outState else
{ ccResult = if szsDisproved exitCode then Just False
:: String -- ^ binary name
-> Bool -- ^ save problem
-> String -- ^ filename without extension
-> IO (String, [String], Int)
runDarwinProcess bin saveTPTP options tmpFileName prob = do
let tmpFile = basename tmpFileName ++ ".tptp"
when saveTPTP (writeFile tmpFile prob)
noProg <- missingExecutableInPath bin
return (bin ++ " not found. Check your $PATH", [], -1)
temp <- getTemporaryDirectory
timeTmpFile <- writeTempFile prob temp tmpFile
readProcessWithExitCode bin (words options ++ [timeTmpFile]) ""
(res, _, tUsed) = parseOutput l
-- removeFile timeTmpFile
-- ^ logical part containing the input Sign and axioms and possibly
-- goals that have been proved earlier as additional axioms
-> GenericConfig ProofTree -- ^ configuration to use
-> Bool -- ^ True means save TPTP file
-> String -- ^ name of the theory in the DevGraph
-> IO (ATPRetval, GenericConfig ProofTree)
-- ^ (retval, configuration with proof status and complete output)
runDarwin b sps cfg saveTPTP thName nGoal = do
extraOptions = maybe "-pc false"
(("-pc false -to " ++) . show) (timeLimit cfg)
prob <- showTPTPProblem thName sps nGoal
$ options ++ ["Requested prover: " ++ bin]
(exitCode, out, tUsed) <-
runDarwinProcess bin saveTPTP extraOptions tmpFileName prob
let ctime = timeToTimeOfDay $ secondsToDiffTime $ toInteger tUsed
(err, retval) = case () of
_ | szsProved exitCode -> (ATPSuccess, provedStatus)
_ | szsDisproved exitCode -> (ATPSuccess, disProvedStatus)
_ | szsTimeout exitCode ->
(ATPTLimitExceeded, defaultProofStatus)
_ | szsStopped exitCode ->
(ATPBatchStopped, defaultProofStatus)
_ -> (ATPError exitCode, defaultProofStatus)
, tacticScript = TacticScript $ show ATPTacticScript
{tsTimeLimit = configTimeLimit cfg,
disProvedStatus = defaultProofStatus {goalStatus = Disproved}
provedStatus = defaultProofStatus
, goalStatus = Proved True
, usedTime = timeToTimeOfDay $ secondsToDiffTime $ toInteger tUsed
fl = formulaLists $ initialLogicalPart sps
fs = concatMap formulae $ filter isAxiomFormula fl
return (err, cfg {proofStatus = retval,
isAxiomFormula :: SPFormulaList -> Bool
getSZSStatusWord :: String -> Maybe String
getSZSStatusWord line = case words
$ fromMaybe (fromMaybe "" $ stripPrefix "% SZS status" line)
$ stripPrefix "SZS status" line of
parseOutput :: [String] -> (String, Bool, Int)
-- ^ (exit code, status found, used time)
parseOutput = foldl checkLine ("", False, -1) where
checkLine (exCode, stateFound, to) line =
if isPrefixOf "Couldn't find eprover" line
|| isInfixOf "darwin -h for further information" line
-- error by running darwin.
then (line, stateFound, to)
else case getSZSStatusWord line of
Just szsState | not stateFound ->
_ -> if "CPU Time" `isPrefixOf` line -- get cpu time
then let time = case takeWhile isDigit $ last (words line) of
in (exCode, stateFound, time)
else (exCode, stateFound, to)