Skip to content

Commit

Permalink
Docs target & table of modules
Browse files Browse the repository at this point in the history
  • Loading branch information
dahlia committed Mar 9, 2017
1 parent d0fa274 commit 1822eb7
Show file tree
Hide file tree
Showing 3 changed files with 63 additions and 0 deletions.
4 changes: 4 additions & 0 deletions nirum.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -45,10 +45,13 @@ library
, Nirum.Package.ModuleSet
, Nirum.Parser
, Nirum.Targets
, Nirum.Targets.Docs
, Nirum.Targets.List
, Nirum.Targets.Python
, Nirum.Version
build-depends: base >=4.7 && <5
, blaze-html
-- only for rendering shakespeare's markup tree
, bytestring
, cmark >=0.5 && <0.6
, containers >=0.5.6.2 && <0.6
Expand All @@ -63,6 +66,7 @@ library
, parsec
-- only for dealing with htoml's ParserError
, semver >=0.3.0 && <1.0
, shakespeare >=2.0.12 && <2.1
, template-haskell >=2.11 && <3
, text >=0.9.1.0 && <1.3
, unordered-containers
Expand Down
1 change: 1 addition & 0 deletions src/Nirum/Targets.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ import Nirum.Package.Metadata ( Metadata (Metadata, target)
, TargetName
)
import Nirum.Targets.List (targetProxyMapQ)
import Nirum.Targets.Docs ()
import Nirum.Targets.Python ()

data BuildError = TargetNameError TargetName
Expand Down
58 changes: 58 additions & 0 deletions src/Nirum/Targets/Docs.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
{-# LANGUAGE OverloadedLists, OverloadedStrings, QuasiQuotes, TypeFamilies #-}
module Nirum.Targets.Docs (Docs) where

import Data.ByteString.Lazy (toStrict)
import Data.Map.Strict (Map)
import Data.Text (Text)
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
import Text.Hamlet (Html, shamlet)

import Nirum.Constructs (Construct (toCode))
import Nirum.Package (Package (Package, metadata, modules))
import Nirum.Package.Metadata ( Author (Author, name)
, Metadata (authors)
, Target ( CompileError
, CompileResult
, compilePackage
, parseTarget
, showCompileError
, targetName
, toByteString
)
)
import qualified Nirum.Package.ModuleSet as MS
import Nirum.Version (versionText)

data Docs = Docs deriving (Eq, Ord, Show)

type Error = Text

index :: Package Docs -> Html
index Package { metadata = md, modules = ms } = [shamlet|
$doctype 5
<html>
<head>
<meta charset="utf-8">
<title>Package docs
<meta name="generator" content="Nirum #{versionText}">
$forall Author { name = name' } <- authors md
<meta name="author" content="#{name'}">
<body>
<h1>Modules
<ul>
$forall (modulePath, _) <- MS.toAscList ms
<li><code>#{toCode modulePath}</code>
|]

compilePackage' :: Package Docs -> Map FilePath (Either Error Html)
compilePackage' pkg =
[("index.html", Right $ index pkg)]

instance Target Docs where
type CompileResult Docs = Html
type CompileError Docs = Error
targetName _ = "docs"
parseTarget _ = return Docs
compilePackage = compilePackage'
showCompileError _ = id
toByteString _ = toStrict . renderHtml

0 comments on commit 1822eb7

Please sign in to comment.