module Scyther.Theory.Html (
GenerationInput(..)
, theoryToHtml
, evalHtmlMarkup
) where
import Data.Char
import Data.Maybe
import qualified Data.Set as S
import qualified Data.Map as M
import Data.Time.Clock
import Data.Time.Format ()
import Data.Traversable (sequenceA)
import Control.Basics
import Control.Monad.Identity
import Control.Monad.State
import Control.Monad.Label
import Control.Concurrent.ManagedThreads
import Text.Isar
import Text.Dot
import Text.HTML.TagSoup
import Text.JSON
import System.IO
import System.Directory
import System.FilePath
import System.Timing
import Extension.Prelude
import Scyther.Protocol
import Scyther.Sequent
import Scyther.Theory
import Scyther.Theory.Dot
import Scyther.Theory.Pretty
indentedToHtmlString :: String -> String
indentedToHtmlString = unlines . map (addBreak . indent) . lines
where
addBreak = (++"<br />")
indent = uncurry (++) . (concatMap (const " ") *** escapeText) . span isSpace
escapeText = renderTags . parseTags
data GenerationInput = GenerationInput {
giHeader :: String
, giTime :: UTCTime
, giSystem :: String
, giInputFile :: FilePath
, giTemplate :: FilePath
, giOutDir :: FilePath
, giMarkup :: HtmlMarkup Doc
, giProofScript :: FilePath -> String
, giDotTool :: String
, giCmdLine :: String
, giIsabelle :: Maybe (FilePath -> IO (IO String, Maybe String))
}
data PathInfo = PathInfo {
inputFileCopy :: FilePath
, proofScriptFile :: FilePath
, logFileCopy :: FilePath
, outDir :: FilePath
, imageDir :: FilePath
, filesDir :: FilePath
}
pathInfo :: GenerationInput -> PathInfo
pathInfo input = info
where
info = PathInfo
{ inputFileCopy = filesDir info </> takeFileName (giInputFile input)
, proofScriptFile = filesDir info </>
addExtension (takeBaseName (giInputFile input) ++ "_cert_auto") "thy"
, logFileCopy = filesDir info </> "logfile"
, outDir = giOutDir input
, imageDir = "img"
, filesDir = "files"
}
mkAbsolute :: PathInfo -> FilePath -> FilePath
mkAbsolute info = (outDir info </>)
requiredDirs :: PathInfo -> [FilePath]
requiredDirs info = map (mkAbsolute info) [".", imageDir info, filesDir info]
jsGenerationInfo :: GenerationInput
-> NominalDiffTime
-> Maybe (Bool, NominalDiffTime, FilePath)
-> JSObject JSValue
jsGenerationInfo input genTime optCheckInfo = toJSObject $
[ ("header", showJSON . toJSString $ giHeader input)
, ("time", showJSON . toJSString . show $ giTime input)
, ("system", showJSON . toJSString $ giSystem input)
, ("inputFile", showJSON . fileLink $ inputFileCopy paths)
, ("proofScript", showJSON . fileLink $ proofScriptFile paths)
, ("commandLine", showJSON . toJSString $ giCmdLine input)
] ++
checkInfo optCheckInfo
where
paths = pathInfo input
fileLink file = (toJSString (takeFileName file), toJSString file)
genTimeString = "generated in " ++ show genTime
checkInfo Nothing =
[ ("certificateStatus", showJSON . toJSString $ genTimeString) ]
checkInfo (Just (success, checkTime, logFile)) =
[ ( "certificateStatus", showJSON . toJSString $ genTimeString ++ status)
, ( "logFile", showJSON (toJSString "logfile", toJSString logFile))
]
where
status | success = ", successfully checked in " ++ show checkTime
| otherwise = ", CHECK FAILED after " ++ show checkTime
theoryToHtml :: GenerationInput -> IO ()
theoryToHtml input = do
putStrLn ""
putStrLn $ " copying template to output directory: " ++ outDir paths
mapM_ (createDirectoryIfMissing True) $ requiredDirs paths
copyTemplate (giTemplate input) $ outDir paths
copyFile (giInputFile input) (mkAbsolute paths $ inputFileCopy paths)
putStr " generating proof script: " >> hFlush stdout
genTime <- timed_ $ writeAbsolute (proofScriptFile paths)
(giProofScript input $ proofScriptFile paths)
putStrLn $ show genTime
optCheckInfo <- case giIsabelle input of
Nothing -> return Nothing
Just machineCheck -> do
putStr " checking proof script: " >> hFlush stdout
((logFileContents, optErrMsg), checkTime) <- timed $
machineCheck (mkAbsolute paths $ proofScriptFile paths)
putStrLn $ show checkTime
contents <- logFileContents
writeAbsolute (logFileCopy paths) contents
return $ Just (isNothing optErrMsg, checkTime, logFileCopy paths)
let thyJSON = mkThyJSON (jsGenerationInfo input genTime optCheckInfo)
writeAbsolute "theory.js"
(("scytherP_theory_JSON = "++) . show $ showJSObject thyJSON "")
putStrLn " generating visualizations using GraphViz:"
parMkGraphs . sortOn snd $ M.toList graphs
where
paths = pathInfo input
writeAbsolute = writeFile . mkAbsolute paths
(ppThy, (st, graphs)) = runHtmlMarkup $ giMarkup input
thyStr = indentedToHtmlString (render ppThy)
mkThyJSON :: JSObject JSValue -> JSObject JSValue
mkThyJSON genInfo = toJSObject
[ ("theory", showJSON $ toJSString thyStr)
, ("generationInfo", showJSON $ genInfo )
, ("theoremDefs", showJSON $ htmlThmDefs st )
, ("theoremRefs", showJSON $ htmlThmRefs st )
, ("cases", showJSON $ htmlCases st )
, ("proofstates", showJSON $ htmlGraphRefs st )
, ("explanations", showJSON $ swapKeyValue $ htmlExpls st)
]
swapKeyValue m = M.fromList [(y, x) | (x, y) <- M.toList m]
mkGraph (dotStr,idx) msgChan = do
let outFile = mkAbsolute paths (imageDir paths </> ("graph_" ++ show idx))
dotFile = addExtension outFile "dot"
pngFile = addExtension outFile "png"
writeFile dotFile dotStr
graphvizDotToPng (giDotTool input) dotFile pngFile msgChan
removeFile dotFile
parMkGraphs = parCmd_ display . map mkGraph
where
display n i msg = hPutStrLn stdout $ " ["++showPadded i++" of "++show n++"] "++msg
where showPadded x = flushRight (length (show n)) (show x)
copyTemplate :: FilePath
-> FilePath
-> IO ()
copyTemplate templateFile targetDir = do
let templateDir = takeDirectory templateFile
template <- readFile templateFile
let files = filter (not.null) $ lines template
copy file = do
let outPath = targetDir </> file
createDirectoryIfMissing True (takeDirectory outPath)
copyFile (templateDir </> file) outPath
mapM_ copy files
type Attributes = [(String,String)]
withTag :: Document d =>
String
-> Attributes
-> d
-> d
withTag tag atts d =
zeroWidthText ("<" ++ tag ++ attsStr ++ ">") <> d <> zeroWidthText ("</" ++ tag ++ ">")
where
attsStr | null atts = ""
| otherwise = concat [ " "++a++"=\""++v++"\"" | (a,v) <- atts ]
withSpan :: Document d => Attributes -> d -> d
withSpan = withTag "span"
newtype GraphIdx = GraphIdx { getGraphIdx :: Int }
deriving( Eq, Ord, Num, Enum, JSON )
instance Show GraphIdx where
show = show . getGraphIdx
type HtmlCase = (GraphIdx, [((String, Bool), GraphIdx)])
type HtmlSequent = GraphIdx
data HtmlMarkupState = HtmlMarkupState {
htmlCases :: M.Map Int HtmlCase
, htmlThmDefs :: M.Map (String, String) HtmlSequent
, htmlThmRefs :: M.Map Int HtmlSequent
, htmlGraphRefs :: M.Map Int HtmlSequent
, htmlExpls :: M.Map String Int
, htmlNextExplRef :: Int
}
type GraphDesc = String
newtype HtmlMarkup a = HtmlMarkup {
unHtmlMarkup :: StateT HtmlMarkupState
(ConsistentLabelsT GraphDesc GraphIdx Identity) a
}
deriving( Functor, Applicative, Monad )
instance MonadState HtmlMarkupState HtmlMarkup where
get = HtmlMarkup get
put = HtmlMarkup . put
referenceGraph :: Dot a -> HtmlMarkup GraphIdx
referenceGraph = HtmlMarkup . lift . label . showDot
nextIndex :: (Num k, Enum k) => M.Map k v -> k
nextIndex = maybe 0 (succ.fst.fst) . M.maxViewWithKey
insertAtNextIndex :: (Ord k, Enum k, Num k) =>
(HtmlMarkupState -> M.Map k v)
-> (M.Map k v -> HtmlMarkupState -> HtmlMarkupState)
-> v -> HtmlMarkup k
insertAtNextIndex getter setter c = HtmlMarkup $ do
s <- get
let cases = getter s
next = nextIndex cases
put (setter (M.insert next c cases) s)
return next
insertHtmlCase :: HtmlCase -> HtmlMarkup Int
insertHtmlCase = insertAtNextIndex htmlCases (\x s->s {htmlCases = x})
insertGraphRef :: GraphIdx -> HtmlMarkup Int
insertGraphRef = insertAtNextIndex htmlGraphRefs (\x s->s {htmlGraphRefs = x})
insertThmRef :: HtmlSequent -> HtmlMarkup Int
insertThmRef = insertAtNextIndex htmlThmRefs (\x s->s {htmlThmRefs = x})
insertThmDef :: Theorem -> HtmlSequent -> HtmlMarkup (String, String)
insertThmDef thm se = do
let name = (protoName . seProto $ thmSequent thm, thmName thm)
modify (\s -> s { htmlThmDefs = M.insert name se (htmlThmDefs s) })
return name
insertExplanation :: String -> HtmlMarkup Int
insertExplanation e = do
expls <- gets htmlExpls
case M.lookup e expls of
Just ref -> return ref
Nothing -> do
st <- get
let ref = htmlNextExplRef st
put $ st { htmlNextExplRef = succ ref, htmlExpls = M.insert e ref expls }
return ref
htmlSequent :: Sequent -> HtmlMarkup HtmlSequent
htmlSequent = referenceGraph . dotSequentMarked S.empty
htmlCase :: Dot a -> [((String,Bool),Dot b)] -> HtmlMarkup HtmlCase
htmlCase c scs =
(,) <$> referenceGraph c <*>
sequenceA [ (,) info <$> referenceGraph dot | (info, dot) <- scs ]
emptyHtmlMarkupState :: HtmlMarkupState
emptyHtmlMarkupState = HtmlMarkupState M.empty M.empty M.empty M.empty M.empty 0
runHtmlMarkup :: HtmlMarkup a -> (a, (HtmlMarkupState, M.Map GraphDesc GraphIdx))
runHtmlMarkup m =
case runIdentity . flip runConsistentLabelsT [1..] .
flip runStateT emptyHtmlMarkupState . unHtmlMarkup $ m of
((res, st), (_, sequentIdxs)) -> (res, (st, sequentIdxs))
evalHtmlMarkup :: HtmlMarkup a -> a
evalHtmlMarkup = fst . runHtmlMarkup
instance MarkupMonad HtmlMarkup where
withGraph dot d = do
ref <- insertGraphRef =<< referenceGraph dot
withSpan [("id", "graphRef_"++show ref)] d
withExplanation expl d = do
ref <- insertExplanation expl
withSpan [("name", "explRef_"++show ref)] d
noteCases c ntcs tcs d = do
let addTag isTrivial (name, dot) = ((name, isTrivial), dot)
cases = map (addTag False) ntcs ++ map (addTag True) tcs
ref <- insertHtmlCase =<< htmlCase c cases
withSpan [("id", "caseRef_"++show ref)] d
theoremRef proto thmname = do
let pname = protoName proto
defs <- gets htmlThmDefs
case M.lookup (pname, thmname) defs of
Just se -> do
ref <- insertThmRef se
withSpan [("id","thmRef_"++show ref)] (text thmname)
Nothing ->
text thmname
theoremDef thm d = do
(pname, thname) <- insertThmDef thm =<< htmlSequent (thmSequent thm)
let anchor = pname ++ "_" ++ thname
withTag "a" [("name",anchor)] d
keyword tag d = withSpan [("class","kw-"++tag)] d