Skip to content

Commit

Permalink
Fix build of hakyll site
Browse files Browse the repository at this point in the history
  • Loading branch information
adamgundry committed Oct 20, 2023
1 parent c254a51 commit 5ea393a
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 23 deletions.
18 changes: 7 additions & 11 deletions hakyll-eventlog/site.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ import Eventlog.Data
import Eventlog.Args
import Eventlog.VegaTemplate
import Eventlog.HtmlTemplate
import Eventlog.Rendering.Types
import Eventlog.Ticky
import Text.Blaze.Html.Renderer.Text
import Options.Applicative
Expand Down Expand Up @@ -109,18 +110,18 @@ eventlogSnippet :: IORef Int -> [T.Text] -> ChartConfig -> IO T.Text
eventlogSnippet c as conf = do
n <- readIORef c
modifyIORef c (+1)
drawEventlog as n conf
drawEventlog as (mkTabID (show n)) conf

drawEventlog :: [T.Text] -> Int -> ChartConfig -> IO T.Text
drawEventlog :: [T.Text] -> TabID -> ChartConfig -> IO T.Text
drawEventlog args vid conf = do
let final_args = ["--no-include-js"] ++ args
Run as <- handleParseResult (execParserPure defaultPrefs argsInfo (map T.unpack final_args))
ty <- generateJson (head $ files as) as
return $ case ty of
HeapProfile (_, dat, _, _) ->
return $ case eventlogHeapProfile ty of
Just (HeapProfileData dat _ _) ->
let itd = if traces conf then TraceData else NoTraceData
in TL.toStrict $ renderHtml $ renderChartWithJson itd (chartType conf) vid dat (vegaJsonText conf)
TickyProfile {} -> mempty
Nothing -> mempty

def :: ChartConfig
def = ChartConfig 600 500 True "category20" "set1" (AreaChart Stacked) Nothing
Expand Down Expand Up @@ -167,9 +168,4 @@ fullEventLogPage file = do
Run as <- handleParseResult (execParserPure defaultPrefs argsInfo
[file, "--no-include-js", "--include-trace-events", "--limit-detailed=100"])
ty <- generateJson file as
case ty of
HeapProfile (header, data_json, descs, closure_descs) ->
return $ templateString header data_json descs closure_descs as
TickyProfile (header, tallocs, ticked_per, dat) ->
return $ tickyTemplateString header tallocs ticked_per dat as

return $ templateString ty as
3 changes: 1 addition & 2 deletions main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,7 @@ doOneJson a fin fout = do
doOneHtml :: Args -> FilePath -> FilePath -> IO ()
doOneHtml a fin fout = do
prof_type <- generateJsonValidate checkTraces fin a
let h = eventlogHeader prof_type
let html = templateString h (eventlogHeapProfile prof_type) (eventlogTickyProfile prof_type) a
let html = templateString prof_type a
writeFile fout html
where
checkTraces :: ProfData -> IO ()
Expand Down
21 changes: 14 additions & 7 deletions src/Eventlog/HtmlTemplate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,8 +130,11 @@ htmlHeader mb_hpd mb_ticky as =
where
has_ticky = isJust mb_ticky

template :: Header -> Maybe HeapProfileData -> Maybe TickyProfileData -> Args -> [TabGroup] -> Html
template header' x y as tab_groups = docTypeHtml $ do
template :: EventlogType
-> Args
-> [TabGroup]
-> Html
template (EventlogType header' x y) as tab_groups = docTypeHtml $ do
H.stringComment $ "Generated with eventlog2html-" <> showVersion version
htmlHeader x y as
body $ H.div ! class_ "container-fluid" $ do
Expand Down Expand Up @@ -204,9 +207,11 @@ renderChartWithJson itd ct k dat vegaSpec = do
renderChart itd ct True k vegaSpec


templateString :: Header -> Maybe HeapProfileData -> Maybe TickyProfileData -> Args -> String
templateString h x y as =
renderHtml $ template h x y as $ allTabs h x y as
templateString :: EventlogType
-> Args
-> String
templateString x as =
renderHtml $ template x as $ allTabs x as


ppHeapProfileType :: HeapProfBreakdown -> Text
Expand All @@ -220,8 +225,10 @@ ppHeapProfileType (HeapProfBreakdownClosureType) = "Basic heap profile (implied
ppHeapProfileType (HeapProfBreakdownInfoTable) = "Info table profile (implied by -hi)"


allTabs :: Header -> Maybe HeapProfileData -> Maybe TickyProfileData -> Args -> [TabGroup]
allTabs h x y as =
allTabs :: EventlogType
-> Args
-> [TabGroup]
allTabs (EventlogType h x y) as =
[SingleTab (metaTab h as)] ++
maybe [] (allHeapTabs h as) x ++
[tickyProfileTabs y]
Expand Down
9 changes: 6 additions & 3 deletions src/Eventlog/Rendering/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,15 @@ data IncludeTraceData
| NoTraceData

-- | Tab IDs must be usable as HTML and Javascript identifiers, so we allow a
-- limited selection of characters. This is enforced only at runtime by the
-- 'IsString' instance, but that seems good enough for now.
-- limited selection of characters. This is enforced only at runtime by
-- 'mkTabID' and the 'IsString' instance, but that seems good enough for now.
newtype TabID = TabID T.Text

instance IsString TabID where
fromString s
fromString = mkTabID

mkTabID :: String -> TabID
mkTabID s
| all valid s = TabID (T.pack s)
| otherwise = error $ "mkTabID: invalid tab ID: " ++ s
where
Expand Down

0 comments on commit 5ea393a

Please sign in to comment.