Skip to content

Commit af01997

Browse files
authored
Merge pull request #128 from dahlia/docs-rst
Generate Python docstrings from docs
2 parents a08853d + 1071db3 commit af01997

File tree

14 files changed

+443
-78
lines changed

14 files changed

+443
-78
lines changed

nirum.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ library
4141
, Nirum.Constructs.TypeExpression
4242
, Nirum.Docs
4343
, Nirum.Docs.Html
44+
, Nirum.Docs.ReStructuredText
4445
, Nirum.Package
4546
, Nirum.Package.Metadata
4647
, Nirum.Package.ModuleSet
@@ -117,6 +118,7 @@ test-suite spec
117118
, Nirum.Constructs.TypeExpressionSpec
118119
, Nirum.DocsSpec
119120
, Nirum.Docs.HtmlSpec
121+
, Nirum.Docs.ReStructuredTextSpec
120122
, Nirum.Package.MetadataSpec
121123
, Nirum.Package.ModuleSetSpec
122124
, Nirum.PackageSpec

src/Nirum/Constructs/Declaration.hs

Lines changed: 17 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,25 @@
1-
module Nirum.Constructs.Declaration ( Declaration
2-
, annotations
3-
, docs
4-
, name
1+
{-# LANGUAGE DefaultSignatures #-}
2+
module Nirum.Constructs.Declaration ( Declaration (annotations, name)
3+
, Documented (docs, docsBlock)
54
) where
65

76
import Nirum.Constructs (Construct)
87
import Nirum.Constructs.Annotation (AnnotationSet, lookupDocs)
9-
import Nirum.Constructs.Docs (Docs)
8+
import Nirum.Constructs.Docs (Docs, toBlock)
109
import Nirum.Constructs.Name (Name)
10+
import Nirum.Docs (Block)
1111

12-
-- 'Construct' which has its own unique 'name' and can has its 'docs'.
13-
class Construct a => Declaration a where
12+
class Documented a where
13+
-- | The docs of the construct.
14+
docs :: a -> Maybe Docs
15+
default docs :: Declaration a => a -> Maybe Docs
16+
docs = lookupDocs . annotations
17+
18+
-- | The parsed docs tree.
19+
docsBlock :: a -> Maybe Block
20+
docsBlock = fmap toBlock . docs
21+
22+
-- Construct which has its own unique 'name' and can has its 'docs'.
23+
class (Construct a, Documented a) => Declaration a where
1424
name :: a -> Name
1525
annotations :: a -> AnnotationSet
16-
17-
docs :: Declaration a => a -> Maybe Docs
18-
docs = lookupDocs . annotations

src/Nirum/Constructs/Module.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,8 +13,9 @@ import Text.InterpolatedString.Perl6 (q)
1313

1414
import Nirum.Constructs (Construct (toCode))
1515
import Nirum.Constructs.Annotation (empty)
16-
import Nirum.Constructs.Docs (Docs)
16+
import Nirum.Constructs.Declaration (Documented (docs))
1717
import qualified Nirum.Constructs.DeclarationSet as DS
18+
import Nirum.Constructs.Docs (Docs)
1819
import Nirum.Constructs.Identifier (Identifier)
1920
import Nirum.Constructs.ModulePath (ModulePath)
2021
import Nirum.Constructs.TypeDeclaration ( JsonType (Boolean, Number, String)
@@ -72,6 +73,9 @@ instance Construct Module where
7273
_ -> True
7374
]
7475

76+
instance Documented Module where
77+
docs (Module _ docs') = docs'
78+
7579
imports :: Module -> M.Map ModulePath (S.Set Identifier)
7680
imports (Module decls _) =
7781
M.fromListWith S.union [(p, [i]) | Import p i _ <- DS.toList decls]

src/Nirum/Constructs/Service.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,9 @@ import qualified Data.Text as T
1313

1414
import Nirum.Constructs (Construct (toCode))
1515
import Nirum.Constructs.Annotation (AnnotationSet, empty, lookupDocs)
16-
import Nirum.Constructs.Declaration (Declaration (annotations, name), docs)
16+
import Nirum.Constructs.Declaration ( Declaration (annotations, name)
17+
, Documented (docs)
18+
)
1719
import Nirum.Constructs.Docs (Docs, toCodeWithPrefix)
1820
import Nirum.Constructs.DeclarationSet (DeclarationSet, toList)
1921
import Nirum.Constructs.Name (Name)
@@ -32,6 +34,8 @@ instance Construct Parameter where
3234
, toCodeWithPrefix "\n" (docs p)
3335
]
3436

37+
instance Documented Parameter
38+
3539
instance Declaration Parameter where
3640
name (Parameter name' _ _) = name'
3741
annotations (Parameter _ _ anno') = anno'
@@ -86,6 +90,8 @@ instance Construct Method where
8690
, "\n"
8791
]
8892

93+
instance Documented Method
94+
8995
instance Declaration Method where
9096
name = methodName
9197
annotations = methodAnnotations

src/Nirum/Constructs/TypeDeclaration.hs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,9 @@ import qualified Data.Text as T
6262

6363
import Nirum.Constructs (Construct (toCode))
6464
import Nirum.Constructs.Annotation as A (AnnotationSet, empty, lookupDocs)
65-
import Nirum.Constructs.Declaration (Declaration (annotations, name), docs)
65+
import Nirum.Constructs.Declaration ( Declaration (annotations, name)
66+
, Documented (docs)
67+
)
6668
import Nirum.Constructs.Docs (Docs (Docs), toCodeWithPrefix)
6769
import Nirum.Constructs.DeclarationSet (DeclarationSet, null', toList)
6870
import Nirum.Constructs.Identifier (Identifier)
@@ -93,6 +95,8 @@ instance Construct EnumMember where
9395
, toCodeWithPrefix "\n" (docs e)
9496
]
9597

98+
instance Documented EnumMember
99+
96100
instance Declaration EnumMember where
97101
name (EnumMember name' _) = name'
98102
annotations (EnumMember _ anno') = anno'
@@ -115,6 +119,8 @@ instance Construct Field where
115119
, toCodeWithPrefix "\n" (docs field)
116120
]
117121

122+
instance Documented Field
123+
118124
instance Declaration Field where
119125
name (Field name' _ _) = name'
120126
annotations (Field _ _ anno') = anno'
@@ -136,6 +142,8 @@ instance Construct Tag where
136142
where
137143
fieldsCode = T.intercalate " " $ map toCode $ toList fields'
138144

145+
instance Documented Tag
146+
139147
instance Declaration Tag where
140148
name (Tag name' _ _) = name'
141149
annotations (Tag _ _ anno') = anno'
@@ -260,6 +268,8 @@ instance Construct TypeDeclaration where
260268
, ");\n"
261269
]
262270

271+
instance Documented TypeDeclaration
272+
263273
instance Declaration TypeDeclaration where
264274
name TypeDeclaration { typename = name' } = name'
265275
name ServiceDeclaration { serviceName = name' } = name'

src/Nirum/Docs/ReStructuredText.hs

Lines changed: 138 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,138 @@
1+
{-# LANGUAGE OverloadedStrings, QuasiQuotes #-}
2+
module Nirum.Docs.ReStructuredText (ReStructuredText, render) where
3+
4+
import qualified Data.Text as T
5+
import Text.InterpolatedString.Perl6 (qq)
6+
7+
import Nirum.Docs
8+
9+
type ReStructuredText = T.Text
10+
11+
renderInline :: Inline -> ReStructuredText
12+
renderInline (Text t) = escape t
13+
renderInline SoftLineBreak = "\n"
14+
renderInline HardLineBreak = "\n"
15+
renderInline (HtmlInline html) = [qq|:raw:`$html`|]
16+
renderInline (Code code') = [qq|``{code'}``|]
17+
renderInline (Emphasis inlines) = [qq|*{escape $ bareText inlines}*|]
18+
renderInline (Strong inlines) = [qq|**{escape $ bareText inlines}**|]
19+
renderInline (Image url title)
20+
| T.null title = T.concat ["\n\n.. image:: ", url, "\n\n"]
21+
| otherwise = T.concat ["\n\n.. image:: ", url, "\n :alt: ", title, "\n\n"]
22+
renderInline (Link url _ inlines)
23+
| length images < length inlines = [qq|`{escape $ bareText inlines} <$url>`_|]
24+
| otherwise = T.replace "\n\n\n\n" "\n\n" $ T.concat [image i | i <- images]
25+
where
26+
images :: [(T.Text, T.Text)]
27+
images = [(url', title) | Image url' title <- inlines]
28+
image :: (T.Text, T.Text) -> ReStructuredText
29+
image (url', title)
30+
| T.null title = T.concat [ "\n\n.. image:: ", url', "\n :target: "
31+
, url, "\n\n"
32+
]
33+
| otherwise = T.concat ["\n\n.. image:: ", url', "\n :alt: ", title
34+
, "\n :target: ", url, "\n\n"]
35+
36+
bareText :: [Inline] -> T.Text
37+
bareText inlines =
38+
T.concat $ map t inlines
39+
where
40+
t :: Inline -> T.Text
41+
t (Text t') = t'
42+
t SoftLineBreak = "\n"
43+
t HardLineBreak = "\n"
44+
t (HtmlInline _) = ""
45+
t (Code code') = code'
46+
t (Emphasis inlines') = bareText inlines'
47+
t (Strong inlines') = bareText inlines'
48+
t (Link _ _ inlines') = bareText inlines'
49+
t (Image _ _) = ""
50+
51+
escape :: T.Text -> ReStructuredText
52+
escape = T.concatMap escapeChar
53+
54+
escapeChar :: Char -> Html
55+
escapeChar '\\' = "\\\\"
56+
escapeChar ':' = "\\:"
57+
escapeChar '`' = "\\`"
58+
escapeChar '.' = "\\."
59+
escapeChar c = T.singleton c
60+
61+
renderInlines :: [Inline] -> ReStructuredText
62+
renderInlines inlines =
63+
T.concat $ prependBar $ map renderInline inlines
64+
where
65+
useLineblocks :: Bool
66+
useLineblocks = not $ null [i | i@HardLineBreak <- inlines]
67+
prependBar :: [ReStructuredText] -> [ReStructuredText]
68+
prependBar ts = if useLineblocks then "| " : ts else ts
69+
70+
indent :: T.Text -> ReStructuredText -> ReStructuredText
71+
indent spaces =
72+
T.intercalate "\n" . map indent' . T.lines
73+
where
74+
indent' :: T.Text -> T.Text
75+
indent' line
76+
| T.null line = T.empty
77+
| otherwise = spaces `T.append` line
78+
79+
indent2 :: ReStructuredText -> ReStructuredText
80+
indent2 = indent " "
81+
82+
indent3 :: ReStructuredText -> ReStructuredText
83+
indent3 = indent " "
84+
85+
indent4 :: ReStructuredText -> ReStructuredText
86+
indent4 = indent " "
87+
88+
renderBlock :: Block -> ReStructuredText
89+
renderBlock (Document blocks) = renderBlocks blocks `T.snoc` '\n'
90+
renderBlock ThematicBreak = "----------"
91+
renderBlock (Paragraph inlines) = renderInlines inlines
92+
renderBlock (BlockQuote blocks) = indent4 (renderBlocks blocks)
93+
renderBlock (HtmlBlock html) =
94+
T.concat [ ".. raw:: html\n\n"
95+
, indent3 html
96+
]
97+
renderBlock (CodeBlock lang code') =
98+
T.concat [ if T.null lang then "::" else [qq|.. code:: $lang|]
99+
, "\n\n"
100+
, indent3 code'
101+
]
102+
renderBlock (Heading level inlines) =
103+
T.concat [text, "\n", T.pack [hChar | _ <- [1 .. (T.length text)]]]
104+
where
105+
text :: ReStructuredText
106+
text = renderInlines inlines
107+
hChar :: Char
108+
hChar = case level of
109+
H1 -> '='
110+
H2 -> '-'
111+
H3 -> '~'
112+
H4 -> '`'
113+
H5 -> '.'
114+
H6 -> '\''
115+
renderBlock (List BulletList (TightItemList items)) =
116+
T.intercalate "\n" [[qq|- {renderInlines i}|] | i <- items]
117+
renderBlock (List BulletList (LooseItemList items)) =
118+
T.intercalate "\n\n" [ [qq|- {T.drop 2 $ indent2 $ renderBlocks i}|]
119+
| i <- items
120+
]
121+
renderBlock (List (OrderedList startNum _) (TightItemList items)) =
122+
T.intercalate "\n" [ [qq|$n. {renderInlines i}|]
123+
| (n, i) <- indexed startNum items
124+
]
125+
renderBlock (List (OrderedList startNum _) (LooseItemList items)) =
126+
T.intercalate "\n\n" [ [qq|$n. {T.drop 3 $ indent3 $ renderBlocks i}|]
127+
| (n, i) <- indexed startNum items
128+
]
129+
130+
indexed :: Enum i => i -> [a] -> [(i, a)]
131+
indexed _ [] = []
132+
indexed start (x : xs) = (start, x) : indexed (succ start) xs
133+
134+
renderBlocks :: [Block] -> ReStructuredText
135+
renderBlocks = T.intercalate "\n\n" . map renderBlock
136+
137+
render :: Block -> ReStructuredText
138+
render = renderBlock

src/Nirum/Package.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -30,10 +30,10 @@ import qualified Data.Set as S
3030
import System.Directory (doesDirectoryExist, listDirectory)
3131
import System.FilePath ((</>))
3232

33-
import Nirum.Constructs.Docs (Docs)
3433
import qualified Nirum.Constructs.DeclarationSet as DS
3534
import Nirum.Constructs.Identifier (Identifier)
3635
import qualified Nirum.Constructs.Module as Mod
36+
import Nirum.Constructs.Declaration (Documented (docs))
3737
import Nirum.Constructs.ModulePath (ModulePath, fromFilePath)
3838
import Nirum.Constructs.TypeDeclaration ( Type
3939
, TypeDeclaration ( Import
@@ -149,8 +149,8 @@ findInBoundModule valueWhenExist valueWhenNotExist
149149
types :: Target t => BoundModule t -> DS.DeclarationSet TypeDeclaration
150150
types = findInBoundModule Mod.types DS.empty
151151

152-
docs :: Target t => BoundModule t -> Maybe Docs
153-
docs = findInBoundModule Mod.docs Nothing
152+
instance Target t => Documented (BoundModule t) where
153+
docs = findInBoundModule Mod.docs Nothing
154154

155155
data TypeLookup = Missing
156156
| Local Type

src/Nirum/Parser.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -427,6 +427,7 @@ tag = do
427427
char ')'
428428
return f
429429
Nothing -> return empty
430+
spaces
430431
docs' <- optional $ do
431432
d <- docs <?> "union tag docs"
432433
spaces

0 commit comments

Comments
 (0)