-- | Classes for 'Documentable' types. module Text.Docs.Class ( -- * @Documentable@ class Documentable (..) , emptydoc , dunlines -- * Specific @Documentable@ class. , DocTitled (..) , DocLinked (..) , DocList (..) ) where import Data.Monoid -- import qualified Text.Html as H -- | Class for types that represents a documentation text. Minimal complete definition: All except 'lnappend'. -- -- Every instance of 'Documentable' class can be an instance of 'Monoid' class. class Documentable a where -- | 'String' to a documentation text. text :: String -> a -- | 'String' to a code format text. code :: String -> a -- | 'String' to a code block. codeblock :: String -> a -- | Emphasizing documentation. emphasize :: a -> a -- | Appending documentation. dappend :: a -> a -> a -- | Appending documentation, with line break. lnappend :: a -> a -> a -- | Rendering documentation. renderdoc :: a -> String -- lnappend x y = x `dappend` text "\n" `dappend` y -- | An empty documentation. emptydoc :: Documentable a => a emptydoc = text [] -- | 'Documentable' version of 'unlines'. dunlines :: Documentable a => [a] -> a dunlines = foldr lnappend emptydoc -- | 'Documentable' types with titles. class Documentable a => DocTitled a where -- | Making a title. title :: a -> a -- | Making a subtitle. subtitle :: a -> a -- title = id subtitle = title -- | 'Documentable' types with links. class Documentable a => DocLinked a where -- | An URL to documentation. url :: String -> a -- | A named URL to documentation. First argument is the name of the link, second argument the URL. nameurl :: String -> String -> a -- url = text nameurl _ y = url y -- | 'Documentable' types with lists. class Documentable a => DocList a where -- | Unordered list. ulist :: [a] -> a -- | Enumerated list. elist :: [a] -> a -- ulist = dunlines . map (dappend $ text "* ") elist = dunlines . zipWith (\n x -> (text $ show n) `dappend` text ". " `dappend` x ) [1..] -- Html instance instance Documentable H.Html where text = H.stringToHtml code = H.thecode . text codeblock = H.pre . text emphasize = H.emphasize dappend = (H.+++) renderdoc = H.renderHtml instance DocTitled H.Html where title = H.h1 subtitle = H.h2 instance DocLinked H.Html where url x = (H.![H.href x]) . H.anchor . text $ x nameurl x y = (H.![H.href y]) . H.anchor . text $ x instance DocList H.Html where ulist = H.ulist . H.concatHtml . map H.li elist = H.olist . H.concatHtml . map H.li