{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} {- LIQUID "--diffcheck" @-} --------------------------------------------------------------------------- -- | This module contains the code that uses the inferred types to generate -- 1. HTMLized source with Inferred Types in mouseover annotations. -- 2. Annotations files (e.g. for vim/emacs) -- 3. JSON files for the web-demo etc. --------------------------------------------------------------------------- module Language.Haskell.Liquid.UX.Annotate (specAnchor, mkOutput, annotate) where import Data.Hashable import Data.String import GHC ( SrcSpan (..) , srcSpanStartCol , srcSpanEndCol , srcSpanStartLine , srcSpanEndLine) import GHC.Exts (groupWith, sortWith) import Prelude hiding (error) import qualified SrcLoc import Text.PrettyPrint.HughesPJ hiding (first) import Text.Printf import Data.Char (isSpace) import Data.Function (on) import Data.List (sortBy) import Data.Maybe (mapMaybe) import Data.Aeson import Control.Arrow hiding ((<+>)) -- import Control.Applicative ((<$>)) import Control.Monad (when, forM_) import System.Exit (ExitCode (..)) import System.FilePath (takeFileName, dropFileName, (>)) import System.Directory (findExecutable, copyFile) import qualified Data.List as L import qualified Data.Vector as V import qualified Data.ByteString.Lazy as B import qualified Data.Text as T import qualified Data.HashMap.Strict as M import qualified Language.Haskell.Liquid.UX.ACSS as ACSS import Language.Haskell.HsColour.Classify import Language.Fixpoint.Utils.Files import Language.Fixpoint.Misc import Language.Haskell.Liquid.GHC.Misc import Language.Fixpoint.Types hiding (panic, Error, Loc, Constant (..), Located (..)) import Language.Haskell.Liquid.Misc import Language.Haskell.Liquid.Types.PrettyPrint import Language.Haskell.Liquid.Types.RefType import Language.Haskell.Liquid.UX.Errors () import Language.Haskell.Liquid.UX.Tidy import Language.Haskell.Liquid.Types hiding (Located(..), Def(..)) import Language.Haskell.Liquid.Types.Specifications -- | @output@ creates the pretty printed output -------------------------------------------------------------------------------------------- mkOutput :: Config -> ErrorResult -> FixSolution -> AnnInfo (Annot SpecType) -> Output Doc -------------------------------------------------------------------------------------------- mkOutput cfg res sol anna = O { o_vars = Nothing -- , o_errors = [] , o_types = toDoc <$> annTy , o_templs = toDoc <$> annTmpl , o_bots = mkBots annTy , o_result = res } where annTmpl = closeAnnots anna annTy = tidySpecType Lossy <$> applySolution sol annTmpl toDoc = rtypeDoc tidy tidy = if shortNames cfg then Lossy else Full -- | @annotate@ actually renders the output to files ------------------------------------------------------------------- annotate :: Config -> [FilePath] -> Output Doc -> IO ACSS.AnnMap ------------------------------------------------------------------- annotate cfg srcFs out = do when showWarns $ forM_ bots (printf "WARNING: Found false in %s\n" . showPpr) when doAnnotate $ mapM_ (doGenerate cfg tplAnnMap typAnnMap annTyp) srcFs return typAnnMap where tplAnnMap = mkAnnMap cfg res annTpl typAnnMap = mkAnnMap cfg res annTyp annTpl = o_templs out annTyp = o_types out res = o_result out bots = o_bots out showWarns = not $ nowarnings cfg doAnnotate = not $ noannotations cfg doGenerate :: Config -> ACSS.AnnMap -> ACSS.AnnMap -> AnnInfo Doc -> FilePath -> IO () doGenerate cfg tplAnnMap typAnnMap annTyp srcF = do generateHtml srcF tpHtmlF tplAnnMap generateHtml srcF tyHtmlF typAnnMap writeFile vimF $ vimAnnot cfg annTyp B.writeFile jsonF $ encode typAnnMap where tyHtmlF = extFileName Html srcF tpHtmlF = extFileName Html $ extFileName Cst srcF _annF = extFileName Annot srcF jsonF = extFileName Json srcF vimF = extFileName Vim srcF mkBots :: Reftable r => AnnInfo (RType c tv r) -> [GHC.SrcSpan] mkBots (AI m) = [ src | (src, (Just _, t) : _) <- sortBy (compare `on` fst) $ M.toList m , isFalse (rTypeReft t) ] writeFilesOrStrings :: FilePath -> [Either FilePath String] -> IO () writeFilesOrStrings tgtFile = mapM_ $ either (`copyFile` tgtFile) (tgtFile `appendFile`) generateHtml :: FilePath -> FilePath -> ACSS.AnnMap -> IO () generateHtml srcF htmlF annm = do src <- readFile srcF let lhs = isExtFile LHs srcF let body = {-# SCC "hsannot" #-} ACSS.hsannot False (Just tokAnnot) lhs (src, annm) cssFile <- getCssPath copyFile cssFile (dropFileName htmlF > takeFileName cssFile) renderHtml lhs htmlF srcF (takeFileName cssFile) body renderHtml :: Bool -> FilePath -> String -> String -> String -> IO () renderHtml True = renderPandoc renderHtml False = renderDirect ------------------------------------------------------------------------- -- | Pandoc HTML Rendering (for lhs + markdown source) ------------------ ------------------------------------------------------------------------- renderPandoc :: FilePath -> String -> String -> String -> IO () renderPandoc htmlFile srcFile css body = do renderFn <- maybe renderDirect renderPandoc' <$> findExecutable "pandoc" renderFn htmlFile srcFile css body renderPandoc' :: FilePath -> FilePath -> FilePath -> String -> String -> IO () renderPandoc' pandocPath htmlFile srcFile css body = do _ <- writeFile mdFile $ pandocPreProc body ec <- executeShellCommand "pandoc" cmd writeFilesOrStrings htmlFile [Right (cssHTML css)] checkExitCode cmd ec where mdFile = extFileName Mkdn srcFile cmd = pandocCmd pandocPath mdFile htmlFile checkExitCode :: Monad m => String -> ExitCode -> m () checkExitCode _ (ExitSuccess) = return () checkExitCode cmd (ExitFailure n) = panic Nothing $ "cmd: " ++ cmd ++ " failure code " ++ show n pandocCmd :: FilePath -> FilePath -> FilePath -> String pandocCmd -- pandocPath mdFile htmlFile = printf "%s -f markdown -t html %s > %s" -- pandocPath mdFile htmlFile pandocPreProc :: String -> String pandocPreProc = T.unpack . strip beg code . strip end code . strip beg spec . strip end spec . T.pack where beg, end, code, spec :: String beg = "begin" end = "end" code = "code" spec = "spec" strip x y = T.replace (T.pack $ printf "\\%s{%s}" x y) T.empty ------------------------------------------------------------------------- -- | Direct HTML Rendering (for non-lhs/markdown source) ---------------- ------------------------------------------------------------------------- -- More or less taken from hscolour renderDirect :: FilePath -> String -> String -> String -> IO () renderDirect htmlFile srcFile css body = writeFile htmlFile $! (topAndTail full srcFile css $! body) where full = True -- False -- TODO: command-line-option -- | @topAndTail True@ is used for standalone HTML; @topAndTail False@ for embedded HTML topAndTail :: Bool -> String -> String -> String -> String topAndTail True title css = (htmlHeader title css ++) . (++ htmlClose) topAndTail False _ _ = id -- Use this for standalone HTML htmlHeader :: String -> String -> String htmlHeader title css = unlines [ "" , "" , "
" , "