Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
  • hpc/hpc-bin
  • arsalan0c/hpc-bin
  • LeoZieger/hpc-bin
  • meooow/hpc-bin
  • wavewave/hpc-bin
  • geo2a/hpc-bin
6 results
Show changes
Commits on Source (3)
......@@ -4,4 +4,4 @@ build:
- "x86_64-linux"
script:
- "cabal update && cabal build -f ci-build -w $GHC"
- "HPC=hpc cabal test -w $GHC"
- "HPC=hpc cabal test -w $GHC --test-option --no-create" # the test option makes sure we do not create missing golden files
# golden files management
.PHONY: update-golden
update-golden:
cp test/Markup/input/Recip/*.html test/Markup/gold/Recip/
......@@ -58,11 +58,11 @@ executable hpc
deepseq >= 1.4.4 && < 1.6,
directory >= 1 && < 1.4,
filepath >= 1 && < 1.6,
containers >= 0.1 && < 0.8,
containers >= 0.1 && < 0.9,
array >= 0.1 && < 0.6,
hpc >= 0.6.2 && < 0.8,
lucid2 ^>= 0.0.20240424,
text ^>= 2.0
text >= 2.0 && < 2.2
if flag(build-tool-depends)
build-tool-depends: happy:happy >= 1.20.0
......@@ -90,11 +90,11 @@ test-suite hpc-test
build-depends:
base >= 4 && < 5
, directory >= 1 && < 1.4
, filepath >= 1 && < 1.5
, filepath >= 1 && < 1.6
, process ^>= 1.6
, tasty ^>= 1.4
, tasty-golden ^>= 2.3
, tasty-hunit ^>= 0.10
, text ^>= 2.0
, text >= 2.0 && < 2.2
, utf8-string ^>= 1.0
default-language: Haskell2010
{-# Language OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings #-}
-- |
-- Module : Trace.Hpc.Markup.Summary
-- Description : Generating the summary html files.
......@@ -7,26 +8,39 @@ module Trace.Hpc.Markup.Summary
name_summary,
fun_summary,
exp_summary,
alt_summary
alt_summary,
)
where
import qualified Lucid as L
import Data.List (sortBy)
import Data.Semigroup as Semi
import System.FilePath ((<.>))
import qualified Data.Text as T
import qualified Lucid as L
import qualified Lucid.Base as L
import Prelude hiding (exp, last)
index_name :: String
index_name = "hpc_index"
index_name = "hpc_index.html"
index_fun :: String
index_fun = "hpc_index_fun"
index_fun = "hpc_index_fun.html"
index_alt :: String
index_alt = "hpc_index_alt"
index_alt = "hpc_index_alt.html"
index_exp :: String
index_exp = "hpc_index_exp"
index_exp = "hpc_index_exp.html"
-- | Legacy non-HTML5 attributes that are missing from Lucid
cellpadding_, cellspacing_, align_, border_ :: T.Text -> L.Attributes
cellpadding_ = L.makeAttributes "cellpadding"
cellspacing_ = L.makeAttributes "cellspacing"
align_ = L.makeAttributes "align"
border_ = L.makeAttributes "border"
-- | A string literal embedded as-is, without escaping
rawStr_ :: T.Text -> L.Html ()
rawStr_ = L.toHtmlRaw
data ModuleSummary = ModuleSummary
{ expTicked :: !Int,
......@@ -38,57 +52,48 @@ data ModuleSummary = ModuleSummary
}
deriving (Show)
showModuleSummary :: (String, String, ModuleSummary) -> String
showModuleSummary (modName, fileName, modSummary) =
"<tr>\n"
<> "<td>&nbsp;&nbsp;<tt>module <a href=\""
<> fileName
<> "\">"
<> modName
<> "</a></tt></td>\n"
<> showSummary (topFunTicked modSummary) (topFunTotal modSummary)
<> showSummary (altTicked modSummary) (altTotal modSummary)
<> showSummary (expTicked modSummary) (expTotal modSummary)
<> "</tr>\n"
showTotalSummary :: ModuleSummary -> String
showTotalSummary modSummary =
"<tr style=\"background: #e0e0e0\">\n"
<> "<th align=left>&nbsp;&nbsp;Program Coverage Total</tt></th>\n"
<> showSummary (topFunTicked modSummary) (topFunTotal modSummary)
<> showSummary (altTicked modSummary) (altTotal modSummary)
<> showSummary (expTicked modSummary) (expTotal modSummary)
<> "</tr>\n"
showSummary :: (Integral t, Show t) => t -> t -> String
showSummary ticked total =
"<td align=\"right\">"
<> showP (percent ticked total)
<> "</td>"
<> "<td>"
<> show ticked
<> "/"
<> show total
<> "</td>"
<> "<td width=100>"
<> ( case percent ticked total of
Nothing -> "&nbsp;"
Just w -> bar w ("bar" :: String)
)
<> "</td>"
showModuleSummary :: (String, String, ModuleSummary) -> L.Html ()
showModuleSummary (modName, fileName, modSummary) = L.tr_ (link <> top <> alt <> exp)
where
link = L.td_ (rawStr_ "&nbsp;&nbsp;" <> L.code_ ("module" <> rawStr_ "&nbsp;" <> L.a_ [L.href_ (T.pack fileName)] (L.toHtml modName)))
top = showSummary (topFunTicked modSummary) (topFunTotal modSummary)
alt = showSummary (altTicked modSummary) (altTotal modSummary)
exp = showSummary (expTicked modSummary) (expTotal modSummary)
showTotalSummary :: ModuleSummary -> L.Html ()
showTotalSummary modSummary = L.tr_ [L.style_ "background: #e0e0e0"] content
where
content = header <> top <> alt <> exp
header = L.th_ [align_ "left"] (rawStr_ "&nbsp;&nbsp;" <> "Program Coverage Total")
top = showSummary (topFunTicked modSummary) (topFunTotal modSummary)
alt = showSummary (altTicked modSummary) (altTotal modSummary)
exp = showSummary (expTicked modSummary) (expTotal modSummary)
showSummary :: Int -> Int -> L.Html ()
showSummary ticked total = percentHtml <> tickedTotal <> last
where
percentHtml :: L.Html ()
percentHtml = L.td_ [align_ "right"] (showP (percent ticked total))
showP :: Maybe Int -> L.Html ()
showP Nothing = "-&nbsp;"
showP (Just x) = show x <> "%"
showP (Just x) = L.toHtml (show x) <> "%"
tickedTotal :: L.Html ()
tickedTotal = L.td_ [] (L.toHtml (show ticked <> "/" <> show total))
last :: L.Html ()
last = L.td_ [L.width_ "100"] (case percent ticked total of Nothing -> "&nbsp;"; Just w -> bar w "bar")
bar :: Int -> String -> L.Html ()
bar 0 _ = bar 100 "invbar"
bar w inner =
"<table cellpadding=0 cellspacing=0 width=\"100\" class=\"bar\">"
<> "<tr><td><table cellpadding=0 cellspacing=0 width=\""
<> show w
<> "%\">"
<> "<tr><td height=12 class="
<> show inner
<> "></td></tr>"
<> "</table></td></tr></table>"
bar w inner = L.table_ [cellpadding_ "0", cellspacing_ "0", L.width_ "100%", L.class_ "bar"] (L.tr_ (L.td_ innerTable))
where
innerTable :: L.Html ()
innerTable = L.table_ [cellpadding_ "0", cellspacing_ "0", L.width_ (T.pack (show w <> "%"))] tableContent
tableContent :: L.Html ()
tableContent = L.tr_ (L.td_ [L.height_ "12", L.class_ (T.pack inner)] "")
percent :: (Integral a) => a -> a -> Maybe a
percent ticked total = if total == 0 then Nothing else Just (ticked * 100 `div` total)
......@@ -111,87 +116,80 @@ instance Monoid ModuleSummary where
summaryHtml :: [(String, String, ModuleSummary)] -> L.Html ()
summaryHtml mods =
L.html_ ((L.toHtmlRaw header) <> (L.toHtmlRaw body))
L.html_ $ header <> body
where
header :: String
header :: L.Html ()
header =
"<head>"
<> "<meta http-equiv=\"Content-Type\" content=\"text/html; charset=UTF-8\">"
<> "<style type=\"text/css\">"
<> "table.bar { background-color: #f25913; }\n"
L.head_ $ do
L.meta_ [L.httpEquiv_ "Content-Type", L.content_ "text/html; charset=UTF-8"]
stylesheet
stylesheet :: L.Html ()
stylesheet = L.style_ [L.type_ "text/css"] stylecontent
stylecontent :: T.Text
stylecontent =
"table.bar { background-color: #f25913; }\n"
<> "td.bar { background-color: #60de51; }\n"
<> "td.invbar { background-color: #f25913; }\n"
<> "table.dashboard { border-collapse: collapse ; border: solid 1px black }\n"
<> ".dashboard td { border: solid 1px black }\n"
<> ".dashboard th { border: solid 1px black }\n"
<> "</style>\n"
<> "</head>"
body :: String
body :: L.Html ()
body =
"<body>"
<> "<table class=\"dashboard\" width=\"100%\" border=1>\n"
<> "<tr>"
<> "<th rowspan=2><a href=\""
<> index_name
<> ".html\">module</a></th>"
<> "<th colspan=3><a href=\""
<> index_fun
<> ".html\">Top Level Definitions</a></th>"
<> "<th colspan=3><a href=\""
<> index_alt
<> ".html\">Alternatives</a></th>"
<> "<th colspan=3><a href=\""
<> index_exp
<> ".html\">Expressions</a></th>"
<> "</tr>"
<> "<tr>"
<> "<th>%</th>"
<> "<th colspan=2>covered / total</th>"
<> "<th>%</th>"
<> "<th colspan=2>covered / total</th>"
<> "<th>%</th>"
<> "<th colspan=2>covered / total</th>"
<> "</tr>"
<> concat
[ showModuleSummary (modName, fileName, modSummary)
| (modName, fileName, modSummary) <- mods
]
<> "<tr></tr>"
<> showTotalSummary
( mconcat
[ modSummary
| (_, _, modSummary) <- mods
]
)
<> "</table></body>"
L.body_ $
L.table_ [L.class_ "dashboard", L.width_ "100%", border_ "1"] $ do
L.tr_ $ do
L.th_ [L.rowspan_ "2"] $ L.a_ [L.href_ (T.pack index_name)] "module"
L.th_ [L.colspan_ "3"] $ L.a_ [L.href_ (T.pack index_fun)] "Top Level Definitions"
L.th_ [L.colspan_ "3"] $ L.a_ [L.href_ (T.pack index_alt)] "Alternatives"
L.th_ [L.colspan_ "3"] $ L.a_ [L.href_ (T.pack index_exp)] "Expressions"
L.tr_ $ do
L.th_ "%" <> L.th_ [L.colspan_ "2"] "covered / total"
L.th_ "%" <> L.th_ [L.colspan_ "2"] "covered / total"
L.th_ "%" <> L.th_ [L.colspan_ "2"] "covered / total"
sequence_
[ showModuleSummary (modName, fileName, modSummary)
| (modName, fileName, modSummary) <- mods
]
L.tr_ ""
showTotalSummary
( mconcat
[ modSummary
| (_, _, modSummary) <- mods
]
)
-- | Compute "hpc_index.html"
name_summary :: [(String, String, ModuleSummary)] -> (FilePath, L.Html ())
name_summary mods = (index_name <.> "html", summaryHtml (sortBy cmp mods))
name_summary mods = (index_name, summaryHtml (sortBy cmp mods))
where
cmp (n1, _, _) (n2, _, _) = compare n1 n2
-- | Compute "hpc_index_fun.html"
fun_summary :: [(String, String, ModuleSummary)] -> (FilePath, L.Html ())
fun_summary mods = (index_fun <.> "html", summaryHtml (sortBy cmp mods))
fun_summary mods = (index_fun, summaryHtml (sortBy cmp mods))
where
cmp (_, _, s1) (_, _, s2) = compare
(percent (topFunTicked s2) (topFunTotal s2))
(percent (topFunTicked s1) (topFunTotal s1))
cmp (_, _, s1) (_, _, s2) =
compare
(percent (topFunTicked s2) (topFunTotal s2))
(percent (topFunTicked s1) (topFunTotal s1))
-- | Compute "hpc_index_alt.html"
alt_summary :: [(String, String, ModuleSummary)] -> (FilePath, L.Html ())
alt_summary mods = (index_alt <.> "html", summaryHtml (sortBy cmp mods))
alt_summary mods = (index_alt, summaryHtml (sortBy cmp mods))
where
cmp (_, _, s1) (_, _, s2) = compare
(percent (altTicked s2) (altTotal s2))
(percent (altTicked s1) (altTotal s1))
cmp (_, _, s1) (_, _, s2) =
compare
(percent (altTicked s2) (altTotal s2))
(percent (altTicked s1) (altTotal s1))
-- | Compute "hpc_index_exp.html"
exp_summary :: [(String, String, ModuleSummary)] -> (FilePath, L.Html ())
exp_summary mods = (index_exp <.> "html", summaryHtml (sortBy cmp mods))
exp_summary mods = (index_exp, summaryHtml (sortBy cmp mods))
where
cmp (_, _, s1) (_, _, s2) = compare
(percent (expTicked s2) (expTotal s2))
(percent (expTicked s1) (expTotal s1))
cmp (_, _, s1) (_, _, s2) =
compare
(percent (expTicked s2) (expTotal s2))
(percent (expTicked s1) (expTotal s1))
module Markup.Tests (markupTests) where
import System.Process
import Control.Monad (void)
import Control.Monad (void, forM_)
import qualified System.FilePath as FP
import Test.Tasty (TestTree, testGroup)
import qualified Data.ByteString.Lazy.UTF8 as BS
......@@ -17,7 +17,7 @@ goldBaseDir = FP.joinPath ["test", "Markup", "gold"]
-- | Tests of the "hpc markup" subcommand
markupTests :: TestTree
markupTests = testGroup "markup" [helpTextTest, recipTest, recipTestIndex]
markupTests = testGroup "markup" [helpTextTest, recipTest, recipTestMarkup]
helpTextTest :: TestTree
helpTextTest = goldenVsString "Help" (goldBaseDir FP.</> "Help.stdout") go
......@@ -39,11 +39,18 @@ recipTest = goldenVsString "RecipStdout" (goldBaseDir FP.</> "Recip.stdout") go
go :: IO BS.ByteString
go = runCommands (inputBaseDir FP.</> "Recip") ["hpc markup Recip.tix"] <* rmHtml
recipTestIndex :: TestTree
recipTestIndex = goldenVsFile "RecipIndexHtml" (goldBaseDir FP.</> "hpc_index.html") (inputBaseDir FP.</> "Recip" FP.</> "hpc_index.html") go
recipTestMarkup :: TestTree
recipTestMarkup =
testGroup "Recip" $ (flip map) filenames $ \fname ->
goldenVsFile fname (recipTestGoldDir FP.</> fname)
(inputBaseDir FP.</> "Recip" FP.</> fname) go
where
filenames = ["hpc_index_alt.html", "hpc_index_fun.html", "hpc_index_exp.html", "Main.hs.html"]
recipTestGoldDir :: FilePath
recipTestGoldDir = goldBaseDir FP.</> "Recip"
go :: IO ()
go = do
_ <- runCommands (inputBaseDir FP.</> "Recip") ["hpc markup Recip.tix"]
rm ["hpc_index_alt.html", "hpc_index_fun.html", "hpc_index_exp.html", "Main.hs.html"]
pure ()
\ No newline at end of file
pure ()
<html>
<head>
<meta http-equiv="Content-Type" content="text/html; charset=UTF-8">
<style type="text/css">
span.lineno { color: white; background: #aaaaaa; border-right: solid white 12px }
span.nottickedoff { background: yellow}
span.istickedoff { background: white }
span.tickonlyfalse { margin: -1px; border: 1px solid #f20913; background: #f20913 }
span.tickonlytrue { margin: -1px; border: 1px solid #60de51; background: #60de51 }
span.funcount { font-size: small; color: orange; z-index: 2; position: absolute; right: 20 }
span.decl { font-weight: bold }
span.spaces { background: white }
</style>
</head>
<body>
<pre>
<span class="decl"><span class="nottickedoff">never executed</span> <span class="tickonlytrue">always true</span> <span class="tickonlyfalse">always false</span></span>
</pre>
<pre>
<span class="lineno"> 1 </span>module Main where
<span class="lineno"> 2 </span>
<span class="lineno"> 3 </span>reciprocal :: Int -&gt; (String, Int)
<span class="lineno"> 4 </span><span class="decl"><span class="istickedoff">reciprocal n | <span class="tickonlytrue">n &gt; 1</span> = ('0' : '.' : digits, recur)</span>
<span class="lineno"> 5 </span><span class="spaces"> </span><span class="istickedoff">| <span class="nottickedoff">otherwise</span> = <span class="nottickedoff">error</span></span>
<span class="lineno"> 6 </span><span class="spaces"> </span><span class="istickedoff"><span class="nottickedoff">&quot;attempting to compute reciprocal of number &lt;= 1&quot;</span></span>
<span class="lineno"> 7 </span><span class="spaces"> </span><span class="istickedoff">where</span>
<span class="lineno"> 8 </span><span class="spaces"> </span><span class="istickedoff">(digits, recur) = divide n 1 []</span></span>
<span class="lineno"> 9 </span>divide :: Int -&gt; Int -&gt; [Int] -&gt; (String, Int)
<span class="lineno"> 10 </span><span class="decl"><span class="istickedoff">divide n c cs | c `elem` cs = ([], position c cs)</span>
<span class="lineno"> 11 </span><span class="spaces"> </span><span class="istickedoff">| r == 0 = (show q, 0)</span>
<span class="lineno"> 12 </span><span class="spaces"> </span><span class="istickedoff">| <span class="tickonlytrue">r /= 0</span> = (show q ++ digits, recur)</span>
<span class="lineno"> 13 </span><span class="spaces"> </span><span class="istickedoff">where</span>
<span class="lineno"> 14 </span><span class="spaces"> </span><span class="istickedoff">(q, r) = (c*10) `quotRem` n</span>
<span class="lineno"> 15 </span><span class="spaces"> </span><span class="istickedoff">(digits, recur) = divide n r (c:cs)</span></span>
<span class="lineno"> 16 </span>
<span class="lineno"> 17 </span>position :: Int -&gt; [Int] -&gt; Int
<span class="lineno"> 18 </span><span class="decl"><span class="istickedoff">position n (x:xs) | n==x = 1</span>
<span class="lineno"> 19 </span><span class="spaces"> </span><span class="istickedoff">| <span class="tickonlytrue">otherwise</span> = 1 + position n xs</span></span>
<span class="lineno"> 20 </span>
<span class="lineno"> 21 </span>showRecip :: Int -&gt; String
<span class="lineno"> 22 </span><span class="decl"><span class="istickedoff">showRecip n =</span>
<span class="lineno"> 23 </span><span class="spaces"> </span><span class="istickedoff">&quot;1/&quot; ++ show n ++ &quot; = &quot; ++</span>
<span class="lineno"> 24 </span><span class="spaces"> </span><span class="istickedoff">if r==0 then d else take p d ++ &quot;(&quot; ++ drop p d ++ &quot;)&quot;</span>
<span class="lineno"> 25 </span><span class="spaces"> </span><span class="istickedoff">where</span>
<span class="lineno"> 26 </span><span class="spaces"> </span><span class="istickedoff">p = length d - r</span>
<span class="lineno"> 27 </span><span class="spaces"> </span><span class="istickedoff">(d, r) = reciprocal n</span></span>
<span class="lineno"> 28 </span>
<span class="lineno"> 29 </span><span class="decl"><span class="istickedoff">main = do</span>
<span class="lineno"> 30 </span><span class="spaces"> </span><span class="istickedoff">number &lt;- readLn</span>
<span class="lineno"> 31 </span><span class="spaces"> </span><span class="istickedoff">putStrLn (showRecip number)</span>
<span class="lineno"> 32 </span><span class="spaces"> </span><span class="istickedoff">main</span></span>
<span class="lineno"> 33 </span>
</pre>
</body>
</html>
<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><style type="text/css">table.bar { background-color: #f25913; }
td.bar { background-color: #60de51; }
td.invbar { background-color: #f25913; }
table.dashboard { border-collapse: collapse ; border: solid 1px black }
.dashboard td { border: solid 1px black }
.dashboard th { border: solid 1px black }
</style></head><body><table class="dashboard" width="100%" border="1"><tr><th rowspan="2"><a href="hpc_index.html">module</a></th><th colspan="3"><a href="hpc_index_fun.html">Top Level Definitions</a></th><th colspan="3"><a href="hpc_index_alt.html">Alternatives</a></th><th colspan="3"><a href="hpc_index_exp.html">Expressions</a></th></tr><tr><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th></tr><tr><td>&nbsp;&nbsp;<code>module&nbsp;<a href="Main.hs.html">Main</a></code></td><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr><tr></tr><tr style="background: #e0e0e0"><th align="left">&nbsp;&nbsp;Program Coverage Total</th><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr></table></body></html>
\ No newline at end of file
<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><style type="text/css">table.bar { background-color: #f25913; }
td.bar { background-color: #60de51; }
td.invbar { background-color: #f25913; }
table.dashboard { border-collapse: collapse ; border: solid 1px black }
.dashboard td { border: solid 1px black }
.dashboard th { border: solid 1px black }
</style></head><body><table class="dashboard" width="100%" border="1"><tr><th rowspan="2"><a href="hpc_index.html">module</a></th><th colspan="3"><a href="hpc_index_fun.html">Top Level Definitions</a></th><th colspan="3"><a href="hpc_index_alt.html">Alternatives</a></th><th colspan="3"><a href="hpc_index_exp.html">Expressions</a></th></tr><tr><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th></tr><tr><td>&nbsp;&nbsp;<code>module&nbsp;<a href="Main.hs.html">Main</a></code></td><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr><tr></tr><tr style="background: #e0e0e0"><th align="left">&nbsp;&nbsp;Program Coverage Total</th><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr></table></body></html>
\ No newline at end of file
<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><style type="text/css">table.bar { background-color: #f25913; }
td.bar { background-color: #60de51; }
td.invbar { background-color: #f25913; }
table.dashboard { border-collapse: collapse ; border: solid 1px black }
.dashboard td { border: solid 1px black }
.dashboard th { border: solid 1px black }
</style></head><body><table class="dashboard" width="100%" border="1"><tr><th rowspan="2"><a href="hpc_index.html">module</a></th><th colspan="3"><a href="hpc_index_fun.html">Top Level Definitions</a></th><th colspan="3"><a href="hpc_index_alt.html">Alternatives</a></th><th colspan="3"><a href="hpc_index_exp.html">Expressions</a></th></tr><tr><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th></tr><tr><td>&nbsp;&nbsp;<code>module&nbsp;<a href="Main.hs.html">Main</a></code></td><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr><tr></tr><tr style="background: #e0e0e0"><th align="left">&nbsp;&nbsp;Program Coverage Total</th><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr></table></body></html>
\ No newline at end of file
<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><style type="text/css">table.bar { background-color: #f25913; }
td.bar { background-color: #60de51; }
td.invbar { background-color: #f25913; }
table.dashboard { border-collapse: collapse ; border: solid 1px black }
.dashboard td { border: solid 1px black }
.dashboard th { border: solid 1px black }
</style></head><body><table class="dashboard" width="100%" border="1"><tr><th rowspan="2"><a href="hpc_index.html">module</a></th><th colspan="3"><a href="hpc_index_fun.html">Top Level Definitions</a></th><th colspan="3"><a href="hpc_index_alt.html">Alternatives</a></th><th colspan="3"><a href="hpc_index_exp.html">Expressions</a></th></tr><tr><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th><th>%</th><th colspan="2">covered / total</th></tr><tr><td>&nbsp;&nbsp;<code>module&nbsp;<a href="Main.hs.html">Main</a></code></td><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr><tr></tr><tr style="background: #e0e0e0"><th align="left">&nbsp;&nbsp;Program Coverage Total</th><td align="right">100%</td><td>5/5</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="100%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="88%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width="100"><table cellpadding="0" cellspacing="0" width="100%" class="bar"><tr><td><table cellpadding="0" cellspacing="0" width="96%"><tr><td height="12" class="bar"></td></tr></table></td></tr></table></td></tr></table></body></html>
\ No newline at end of file
<html><head><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"><style type="text/css">table.bar { background-color: #f25913; }
td.bar { background-color: #60de51; }
td.invbar { background-color: #f25913; }
table.dashboard { border-collapse: collapse ; border: solid 1px black }
.dashboard td { border: solid 1px black }
.dashboard th { border: solid 1px black }
</style>
</head><body><table class="dashboard" width="100%" border=1>
<tr><th rowspan=2><a href="hpc_index.html">module</a></th><th colspan=3><a href="hpc_index_fun.html">Top Level Definitions</a></th><th colspan=3><a href="hpc_index_alt.html">Alternatives</a></th><th colspan=3><a href="hpc_index_exp.html">Expressions</a></th></tr><tr><th>%</th><th colspan=2>covered / total</th><th>%</th><th colspan=2>covered / total</th><th>%</th><th colspan=2>covered / total</th></tr><tr>
<td>&nbsp;&nbsp;<tt>module <a href="Main.hs.html">Main</a></tt></td>
<td align="right">100%</td><td>5/5</td><td width=100><table cellpadding=0 cellspacing=0 width="100" class="bar"><tr><td><table cellpadding=0 cellspacing=0 width="100%"><tr><td height=12 class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width=100><table cellpadding=0 cellspacing=0 width="100" class="bar"><tr><td><table cellpadding=0 cellspacing=0 width="88%"><tr><td height=12 class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width=100><table cellpadding=0 cellspacing=0 width="100" class="bar"><tr><td><table cellpadding=0 cellspacing=0 width="96%"><tr><td height=12 class="bar"></td></tr></table></td></tr></table></td></tr>
<tr></tr><tr style="background: #e0e0e0">
<th align=left>&nbsp;&nbsp;Program Coverage Total</tt></th>
<td align="right">100%</td><td>5/5</td><td width=100><table cellpadding=0 cellspacing=0 width="100" class="bar"><tr><td><table cellpadding=0 cellspacing=0 width="100%"><tr><td height=12 class="bar"></td></tr></table></td></tr></table></td><td align="right">88%</td><td>8/9</td><td width=100><table cellpadding=0 cellspacing=0 width="100" class="bar"><tr><td><table cellpadding=0 cellspacing=0 width="88%"><tr><td height=12 class="bar"></td></tr></table></td></tr></table></td><td align="right">96%</td><td>94/97</td><td width=100><table cellpadding=0 cellspacing=0 width="100" class="bar"><tr><td><table cellpadding=0 cellspacing=0 width="96%"><tr><td height=12 class="bar"></td></tr></table></td></tr></table></td></tr>
</table></body></html>
\ No newline at end of file