{-# LANGUAGE TemplateHaskell, EmptyDataDecls, NoMonomorphismRestriction #-} module Document.Semantics.HtmlNumberedHeaders where import Data.HList.Label4 import Data.HList.TypeEqGeneric1 import Data.HList.TypeCastGeneric1 import Language.Grammars.AspectAG import Language.Grammars.AspectAG.Derive import Document.Decl import Document.Semantics.Html import Document.Semantics.NumberedHeaders -- | Redefines the html attribute for headers so that it will print -- the associated number header_html' = synmodM html $ do level <- at ch_level_header inls <- at ch_inlines_header loc <- at loc let num = loc # headerNum return $ "" ++ formatNH num ++ " " ++ inls # html ++ "" ++ "\n" -- building the record semHtml' = mkDoc' (default_cHeaderNum `ext` blockLcons_html) (default_cHeaderNum `ext` blockLnil_html) bold_html (document_cHeaderNum `ext` document_html) (header_headerNum `ext` header_cHeaderNum `ext` header_html' `ext` header_html) inlineLcons_html inlineLnil_html italics_html (default_cHeaderNum `ext` paragraph_html ) plain_html