diff --git a/nirum.cabal b/nirum.cabal index 8603b7e..4b7281b 100644 --- a/nirum.cabal +++ b/nirum.cabal @@ -41,6 +41,7 @@ library , Nirum.Constructs.TypeExpression , Nirum.Docs , Nirum.Docs.Html + , Nirum.Docs.ReStructuredText , Nirum.Package , Nirum.Package.Metadata , Nirum.Package.ModuleSet @@ -117,6 +118,7 @@ test-suite spec , Nirum.Constructs.TypeExpressionSpec , Nirum.DocsSpec , Nirum.Docs.HtmlSpec + , Nirum.Docs.ReStructuredTextSpec , Nirum.Package.MetadataSpec , Nirum.Package.ModuleSetSpec , Nirum.PackageSpec diff --git a/src/Nirum/Constructs/Declaration.hs b/src/Nirum/Constructs/Declaration.hs index b7ec7cf..badcd50 100644 --- a/src/Nirum/Constructs/Declaration.hs +++ b/src/Nirum/Constructs/Declaration.hs @@ -1,18 +1,25 @@ -module Nirum.Constructs.Declaration ( Declaration - , annotations - , docs - , name +{-# LANGUAGE DefaultSignatures #-} +module Nirum.Constructs.Declaration ( Declaration (annotations, name) + , Documented (docs, docsBlock) ) where import Nirum.Constructs (Construct) import Nirum.Constructs.Annotation (AnnotationSet, lookupDocs) -import Nirum.Constructs.Docs (Docs) +import Nirum.Constructs.Docs (Docs, toBlock) import Nirum.Constructs.Name (Name) +import Nirum.Docs (Block) --- 'Construct' which has its own unique 'name' and can has its 'docs'. -class Construct a => Declaration a where +class Documented a where + -- | The docs of the construct. + docs :: a -> Maybe Docs + default docs :: Declaration a => a -> Maybe Docs + docs = lookupDocs . annotations + + -- | The parsed docs tree. + docsBlock :: a -> Maybe Block + docsBlock = fmap toBlock . docs + +-- Construct which has its own unique 'name' and can has its 'docs'. +class (Construct a, Documented a) => Declaration a where name :: a -> Name annotations :: a -> AnnotationSet - -docs :: Declaration a => a -> Maybe Docs -docs = lookupDocs . annotations diff --git a/src/Nirum/Constructs/Module.hs b/src/Nirum/Constructs/Module.hs index 52ec3a6..8482d5c 100644 --- a/src/Nirum/Constructs/Module.hs +++ b/src/Nirum/Constructs/Module.hs @@ -13,8 +13,9 @@ import Text.InterpolatedString.Perl6 (q) import Nirum.Constructs (Construct (toCode)) import Nirum.Constructs.Annotation (empty) -import Nirum.Constructs.Docs (Docs) +import Nirum.Constructs.Declaration (Documented (docs)) import qualified Nirum.Constructs.DeclarationSet as DS +import Nirum.Constructs.Docs (Docs) import Nirum.Constructs.Identifier (Identifier) import Nirum.Constructs.ModulePath (ModulePath) import Nirum.Constructs.TypeDeclaration ( JsonType (Boolean, Number, String) @@ -72,6 +73,9 @@ instance Construct Module where _ -> True ] +instance Documented Module where + docs (Module _ docs') = docs' + imports :: Module -> M.Map ModulePath (S.Set Identifier) imports (Module decls _) = M.fromListWith S.union [(p, [i]) | Import p i _ <- DS.toList decls] diff --git a/src/Nirum/Constructs/Service.hs b/src/Nirum/Constructs/Service.hs index 73dd523..ffe00fd 100644 --- a/src/Nirum/Constructs/Service.hs +++ b/src/Nirum/Constructs/Service.hs @@ -13,7 +13,9 @@ import qualified Data.Text as T import Nirum.Constructs (Construct (toCode)) import Nirum.Constructs.Annotation (AnnotationSet, empty, lookupDocs) -import Nirum.Constructs.Declaration (Declaration (annotations, name), docs) +import Nirum.Constructs.Declaration ( Declaration (annotations, name) + , Documented (docs) + ) import Nirum.Constructs.Docs (Docs, toCodeWithPrefix) import Nirum.Constructs.DeclarationSet (DeclarationSet, toList) import Nirum.Constructs.Name (Name) @@ -32,6 +34,8 @@ instance Construct Parameter where , toCodeWithPrefix "\n" (docs p) ] +instance Documented Parameter + instance Declaration Parameter where name (Parameter name' _ _) = name' annotations (Parameter _ _ anno') = anno' @@ -86,6 +90,8 @@ instance Construct Method where , "\n" ] +instance Documented Method + instance Declaration Method where name = methodName annotations = methodAnnotations diff --git a/src/Nirum/Constructs/TypeDeclaration.hs b/src/Nirum/Constructs/TypeDeclaration.hs index 781d365..a610877 100644 --- a/src/Nirum/Constructs/TypeDeclaration.hs +++ b/src/Nirum/Constructs/TypeDeclaration.hs @@ -62,7 +62,9 @@ import qualified Data.Text as T import Nirum.Constructs (Construct (toCode)) import Nirum.Constructs.Annotation as A (AnnotationSet, empty, lookupDocs) -import Nirum.Constructs.Declaration (Declaration (annotations, name), docs) +import Nirum.Constructs.Declaration ( Declaration (annotations, name) + , Documented (docs) + ) import Nirum.Constructs.Docs (Docs (Docs), toCodeWithPrefix) import Nirum.Constructs.DeclarationSet (DeclarationSet, null', toList) import Nirum.Constructs.Identifier (Identifier) @@ -93,6 +95,8 @@ instance Construct EnumMember where , toCodeWithPrefix "\n" (docs e) ] +instance Documented EnumMember + instance Declaration EnumMember where name (EnumMember name' _) = name' annotations (EnumMember _ anno') = anno' @@ -115,6 +119,8 @@ instance Construct Field where , toCodeWithPrefix "\n" (docs field) ] +instance Documented Field + instance Declaration Field where name (Field name' _ _) = name' annotations (Field _ _ anno') = anno' @@ -136,6 +142,8 @@ instance Construct Tag where where fieldsCode = T.intercalate " " $ map toCode $ toList fields' +instance Documented Tag + instance Declaration Tag where name (Tag name' _ _) = name' annotations (Tag _ _ anno') = anno' @@ -260,6 +268,8 @@ instance Construct TypeDeclaration where , ");\n" ] +instance Documented TypeDeclaration + instance Declaration TypeDeclaration where name TypeDeclaration { typename = name' } = name' name ServiceDeclaration { serviceName = name' } = name' diff --git a/src/Nirum/Docs/ReStructuredText.hs b/src/Nirum/Docs/ReStructuredText.hs new file mode 100644 index 0000000..65e2854 --- /dev/null +++ b/src/Nirum/Docs/ReStructuredText.hs @@ -0,0 +1,138 @@ +{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} +module Nirum.Docs.ReStructuredText (ReStructuredText, render) where + +import qualified Data.Text as T +import Text.InterpolatedString.Perl6 (qq) + +import Nirum.Docs + +type ReStructuredText = T.Text + +renderInline :: Inline -> ReStructuredText +renderInline (Text t) = escape t +renderInline SoftLineBreak = "\n" +renderInline HardLineBreak = "\n" +renderInline (HtmlInline html) = [qq|:raw:`$html`|] +renderInline (Code code') = [qq|``{code'}``|] +renderInline (Emphasis inlines) = [qq|*{escape $ bareText inlines}*|] +renderInline (Strong inlines) = [qq|**{escape $ bareText inlines}**|] +renderInline (Image url title) + | T.null title = T.concat ["\n\n.. image:: ", url, "\n\n"] + | otherwise = T.concat ["\n\n.. image:: ", url, "\n :alt: ", title, "\n\n"] +renderInline (Link url _ inlines) + | length images < length inlines = [qq|`{escape $ bareText inlines} <$url>`_|] + | otherwise = T.replace "\n\n\n\n" "\n\n" $ T.concat [image i | i <- images] + where + images :: [(T.Text, T.Text)] + images = [(url', title) | Image url' title <- inlines] + image :: (T.Text, T.Text) -> ReStructuredText + image (url', title) + | T.null title = T.concat [ "\n\n.. image:: ", url', "\n :target: " + , url, "\n\n" + ] + | otherwise = T.concat ["\n\n.. image:: ", url', "\n :alt: ", title + , "\n :target: ", url, "\n\n"] + +bareText :: [Inline] -> T.Text +bareText inlines = + T.concat $ map t inlines + where + t :: Inline -> T.Text + t (Text t') = t' + t SoftLineBreak = "\n" + t HardLineBreak = "\n" + t (HtmlInline _) = "" + t (Code code') = code' + t (Emphasis inlines') = bareText inlines' + t (Strong inlines') = bareText inlines' + t (Link _ _ inlines') = bareText inlines' + t (Image _ _) = "" + +escape :: T.Text -> ReStructuredText +escape = T.concatMap escapeChar + +escapeChar :: Char -> Html +escapeChar '\\' = "\\\\" +escapeChar ':' = "\\:" +escapeChar '`' = "\\`" +escapeChar '.' = "\\." +escapeChar c = T.singleton c + +renderInlines :: [Inline] -> ReStructuredText +renderInlines inlines = + T.concat $ prependBar $ map renderInline inlines + where + useLineblocks :: Bool + useLineblocks = not $ null [i | i@HardLineBreak <- inlines] + prependBar :: [ReStructuredText] -> [ReStructuredText] + prependBar ts = if useLineblocks then "| " : ts else ts + +indent :: T.Text -> ReStructuredText -> ReStructuredText +indent spaces = + T.intercalate "\n" . map indent' . T.lines + where + indent' :: T.Text -> T.Text + indent' line + | T.null line = T.empty + | otherwise = spaces `T.append` line + +indent2 :: ReStructuredText -> ReStructuredText +indent2 = indent " " + +indent3 :: ReStructuredText -> ReStructuredText +indent3 = indent " " + +indent4 :: ReStructuredText -> ReStructuredText +indent4 = indent " " + +renderBlock :: Block -> ReStructuredText +renderBlock (Document blocks) = renderBlocks blocks `T.snoc` '\n' +renderBlock ThematicBreak = "----------" +renderBlock (Paragraph inlines) = renderInlines inlines +renderBlock (BlockQuote blocks) = indent4 (renderBlocks blocks) +renderBlock (HtmlBlock html) = + T.concat [ ".. raw:: html\n\n" + , indent3 html + ] +renderBlock (CodeBlock lang code') = + T.concat [ if T.null lang then "::" else [qq|.. code:: $lang|] + , "\n\n" + , indent3 code' + ] +renderBlock (Heading level inlines) = + T.concat [text, "\n", T.pack [hChar | _ <- [1 .. (T.length text)]]] + where + text :: ReStructuredText + text = renderInlines inlines + hChar :: Char + hChar = case level of + H1 -> '=' + H2 -> '-' + H3 -> '~' + H4 -> '`' + H5 -> '.' + H6 -> '\'' +renderBlock (List BulletList (TightItemList items)) = + T.intercalate "\n" [[qq|- {renderInlines i}|] | i <- items] +renderBlock (List BulletList (LooseItemList items)) = + T.intercalate "\n\n" [ [qq|- {T.drop 2 $ indent2 $ renderBlocks i}|] + | i <- items + ] +renderBlock (List (OrderedList startNum _) (TightItemList items)) = + T.intercalate "\n" [ [qq|$n. {renderInlines i}|] + | (n, i) <- indexed startNum items + ] +renderBlock (List (OrderedList startNum _) (LooseItemList items)) = + T.intercalate "\n\n" [ [qq|$n. {T.drop 3 $ indent3 $ renderBlocks i}|] + | (n, i) <- indexed startNum items + ] + +indexed :: Enum i => i -> [a] -> [(i, a)] +indexed _ [] = [] +indexed start (x : xs) = (start, x) : indexed (succ start) xs + +renderBlocks :: [Block] -> ReStructuredText +renderBlocks = T.intercalate "\n\n" . map renderBlock + +render :: Block -> ReStructuredText +render = renderBlock diff --git a/src/Nirum/Package.hs b/src/Nirum/Package.hs index c7a57f7..470d652 100644 --- a/src/Nirum/Package.hs +++ b/src/Nirum/Package.hs @@ -30,10 +30,10 @@ import qualified Data.Set as S import System.Directory (doesDirectoryExist, listDirectory) import System.FilePath (()) -import Nirum.Constructs.Docs (Docs) import qualified Nirum.Constructs.DeclarationSet as DS import Nirum.Constructs.Identifier (Identifier) import qualified Nirum.Constructs.Module as Mod +import Nirum.Constructs.Declaration (Documented (docs)) import Nirum.Constructs.ModulePath (ModulePath, fromFilePath) import Nirum.Constructs.TypeDeclaration ( Type , TypeDeclaration ( Import @@ -149,8 +149,8 @@ findInBoundModule valueWhenExist valueWhenNotExist types :: Target t => BoundModule t -> DS.DeclarationSet TypeDeclaration types = findInBoundModule Mod.types DS.empty -docs :: Target t => BoundModule t -> Maybe Docs -docs = findInBoundModule Mod.docs Nothing +instance Target t => Documented (BoundModule t) where + docs = findInBoundModule Mod.docs Nothing data TypeLookup = Missing | Local Type diff --git a/src/Nirum/Parser.hs b/src/Nirum/Parser.hs index b7a0827..49c605b 100644 --- a/src/Nirum/Parser.hs +++ b/src/Nirum/Parser.hs @@ -427,6 +427,7 @@ tag = do char ')' return f Nothing -> return empty + spaces docs' <- optional $ do d <- docs "union tag docs" spaces diff --git a/src/Nirum/Targets/Python.hs b/src/Nirum/Targets/Python.hs index 52cab97..caa9b93 100644 --- a/src/Nirum/Targets/Python.hs +++ b/src/Nirum/Targets/Python.hs @@ -63,6 +63,7 @@ import Text.InterpolatedString.Perl6 (q, qq) import qualified Nirum.CodeGen as C import Nirum.CodeGen (Failure) +import Nirum.Constructs.Declaration (Documented (docsBlock)) import qualified Nirum.Constructs.DeclarationSet as DS import qualified Nirum.Constructs.Identifier as I import Nirum.Constructs.ModulePath ( ModulePath @@ -101,6 +102,7 @@ import Nirum.Constructs.TypeExpression ( TypeExpression ( ListModifier , TypeIdentifier ) ) +import Nirum.Docs.ReStructuredText (ReStructuredText, render) import Nirum.Package ( BoundModule , Package (Package, metadata, modules) , TypeLookup (Imported, Local, Missing) @@ -302,6 +304,58 @@ toIndentedCodes f traversable concatenator = quote :: T.Text -> T.Text quote s = [qq|'{s}'|] +compileDocs :: Documented a => a -> Maybe ReStructuredText +compileDocs = fmap render . docsBlock + +quoteDocstring :: ReStructuredText -> Code +quoteDocstring rst = T.concat ["r'''", rst, "\n'''\n"] + +compileDocstring' :: Documented a => Code -> a -> [ReStructuredText] -> Code +compileDocstring' indentSpace d extra = + case (compileDocs d, extra) of + (Nothing, []) -> "\n" + (result, extra') -> indent indentSpace $ quoteDocstring $ + T.append (fromMaybe "" result) $ + T.concat ['\n' `T.cons` e `T.snoc` '\n' | e <- extra'] + +compileDocstring :: Documented a => Code -> a -> Code +compileDocstring indentSpace d = compileDocstring' indentSpace d [] + +compileDocstringWithFields :: Documented a + => Code -> a -> DS.DeclarationSet Field -> Code +compileDocstringWithFields indentSpace decl fields = + compileDocstring' indentSpace decl extra + where + extra :: [ReStructuredText] + extra = + [ case compileDocs f of + Nothing -> T.concat [ ".. attribute:: " + , toAttributeName' n + , "\n" + ] + Just docs' -> T.concat [ ".. attribute:: " + , toAttributeName' n + , "\n\n" + , indent " " docs' + ] + | f@(Field n _ _) <- toList fields + ] + +compileDocsComment :: Documented a => Code -> a -> Code +compileDocsComment indentSpace d = + case compileDocs d of + Nothing -> "\n" + Just rst -> indent (indentSpace `T.append` "#: ") rst + +indent :: Code -> Code -> Code +indent space = + T.intercalate "\n" . map indentLn . T.lines + where + indentLn :: Code -> Code + indentLn line + | T.null line = T.empty + | otherwise = space `T.append` line + typeReprCompiler :: CodeGen (Code -> Code) typeReprCompiler = do ver <- getPythonVersion @@ -329,12 +383,8 @@ returnCompiler = do Python2 -> "" Python3 -> [qq| -> $r|] -compileUnionTag :: Source - -> Name - -> Name - -> DS.DeclarationSet Field - -> CodeGen Code -compileUnionTag source parentname typename' fields = do +compileUnionTag :: Source -> Name -> Tag -> CodeGen Code +compileUnionTag source parentname d@(Tag typename' fields _) = do typeExprCodes <- mapM (compileTypeExpression source) [typeExpr | (Field _ typeExpr _) <- toList fields] let className = toClassName' typename' @@ -367,8 +417,7 @@ compileUnionTag source parentname typename' fields = do ret <- returnCompiler return [qq| class $className($parentClass): - # TODO: docstring - +{compileDocstringWithFields " " d fields} __slots__ = ( $slots ) @@ -469,15 +518,23 @@ compileTypeExpression source modifier = do compileTypeDeclaration :: Source -> TypeDeclaration -> CodeGen Code compileTypeDeclaration _ TypeDeclaration { type' = PrimitiveType {} } = return "" -- never used -compileTypeDeclaration src TypeDeclaration { typename = typename' - , type' = Alias ctype } = do +compileTypeDeclaration src d@TypeDeclaration { typename = typename' + , type' = Alias ctype + } = do ctypeExpr <- compileTypeExpression src ctype return [qq| -# TODO: docstring +$docsComment {toClassName' typename'} = $ctypeExpr |] -compileTypeDeclaration src TypeDeclaration { typename = typename' - , type' = UnboxedType itype } = do + where + docsComment :: Code + docsComment = + case compileDocs d of + Nothing -> "" + Just rst -> indent "#: " rst +compileTypeDeclaration src d@TypeDeclaration { typename = typename' + , type' = UnboxedType itype + } = do let className = toClassName' typename' itypeExpr <- compileTypeExpression src itype insertThirdPartyImports [ ("nirum.validate", ["validate_boxed_type"]) @@ -489,8 +546,7 @@ compileTypeDeclaration src TypeDeclaration { typename = typename' ret <- returnCompiler return [qq| class $className(object): - # TODO: docstring - +{compileDocstring " " d} __nirum_inner_type__ = $itypeExpr def __init__(self, { arg "value" itypeExpr }){ ret "None" }: @@ -525,22 +581,29 @@ class $className(object): def __hash__(self){ ret "int" }: return hash(self.value) |] -compileTypeDeclaration _ TypeDeclaration { typename = typename' - , type' = EnumType members } = do +compileTypeDeclaration _ d@TypeDeclaration { typename = typename' + , type' = EnumType members + } = do let className = toClassName' typename' memberNames = T.intercalate - "\n " - [ [qq|{toAttributeName' memberName} = '{I.toSnakeCaseText bn}'|] - | EnumMember memberName@(Name _ bn) _ <- toList members + "\n" + [ T.concat [ compileDocsComment " " m + , "\n " + , toAttributeName' memberName + , " = '" + , I.toSnakeCaseText bn + , "'" + ] + | m@(EnumMember memberName@(Name _ bn) _) <- toList members ] insertEnumImport arg <- parameterCompiler ret <- returnCompiler return [qq| class $className(enum.Enum): - # TODO: docstring +{compileDocstring " " d} - $memberNames +$memberNames def __nirum_serialize__(self){ ret "str" }: return self.value @@ -552,19 +615,21 @@ class $className(enum.Enum): ){ ret $ quote className }: return cls(value.replace('-', '_')) # FIXME: validate input |] -compileTypeDeclaration src TypeDeclaration { typename = typename' - , type' = RecordType fields } = do - typeExprCodes <- mapM (compileTypeExpression src) - [typeExpr | (Field _ typeExpr _) <- toList fields] +compileTypeDeclaration src d@TypeDeclaration { typename = typename' + , type' = RecordType fields + } = do let className = toClassName' typename' - fieldNames = map toAttributeName' [ name' - | (Field name' _ _) <- toList fields + fieldList = toList fields + typeExprCodes <- mapM (compileTypeExpression src) + [typeExpr | (Field _ typeExpr _) <- fieldList] + let fieldNames = map toAttributeName' [ name' + | (Field name' _ _) <- fieldList ] - nameNTypes = zip fieldNames typeExprCodes + nameTypePairs = zip fieldNames typeExprCodes slotTypes = toIndentedCodes - (\ (n, t) -> [qq|'{n}': {t}|]) nameNTypes ",\n " + (\ (n, t) -> [qq|'{n}': {t}|]) nameTypePairs ",\n " slots = toIndentedCodes (\ n -> [qq|'{n}'|]) fieldNames ",\n " - initialArgs gen = toIndentedCodes (uncurry gen) nameNTypes ", " + initialArgs gen = toIndentedCodes (uncurry gen) nameTypePairs ", " initialValues = toIndentedCodes (\ n -> [qq|self.{n} = {n}|]) fieldNames "\n " nameMaps = toIndentedCodes @@ -584,8 +649,7 @@ compileTypeDeclaration src TypeDeclaration { typename = typename' let clsType = arg "cls" "type" return [qq| class $className(object): - # TODO: docstring - +{compileDocstringWithFields " " d fields} __slots__ = ( $slots, ) @@ -629,11 +693,12 @@ class $className(object): def __hash__(self){ret "int"}: return hash(($hashText,)) |] -compileTypeDeclaration src TypeDeclaration { typename = typename' - , type' = UnionType tags } = do - fieldCodes <- mapM (uncurry (compileUnionTag src typename')) tagNameNFields +compileTypeDeclaration src d@TypeDeclaration { typename = typename' + , type' = UnionType tags + } = do + tagCodes <- mapM (compileUnionTag src typename') $ toList tags let className = toClassName' typename' - fieldCodes' = T.intercalate "\n\n" fieldCodes + tagCodes' = T.intercalate "\n\n" tagCodes enumMembers = toIndentedCodes (\ (t, b) -> [qq|$t = '{b}'|]) enumMembers' "\n " importTypingForPython3 @@ -647,6 +712,7 @@ compileTypeDeclaration src TypeDeclaration { typename = typename' arg <- parameterCompiler return [qq| class $className(object): +{compileDocstring " " d} __nirum_union_behind_name__ = '{I.toSnakeCaseText $ N.behindName typename'}' __nirum_field_names__ = name_dict_type([ @@ -673,13 +739,9 @@ class $className(object): return deserialize_union_type(cls, value) -$fieldCodes' +$tagCodes' |] where - tagNameNFields :: [(Name, DS.DeclarationSet Field)] - tagNameNFields = [ (tagName, fields) - | (Tag tagName fields _) <- toList tags - ] enumMembers' :: [(T.Text, T.Text)] enumMembers' = [ ( toAttributeName' tagName , I.toSnakeCaseText $ N.behindName tagName @@ -689,13 +751,13 @@ $fieldCodes' nameMaps :: T.Text nameMaps = toIndentedCodes toNamePair - [name' | (name', _) <- tagNameNFields] + [name' | Tag name' _ _ <- toList tags] ",\n " compileTypeDeclaration src@Source { sourcePackage = Package { metadata = metadata' } } - ServiceDeclaration { serviceName = name' - , service = Service methods - } = do + d@ServiceDeclaration { serviceName = name' + , service = Service methods + } = do let methods' = toList methods methodMetadata <- mapM compileMethodMetadata methods' let methodMetadata' = commaNl methodMetadata @@ -713,7 +775,7 @@ compileTypeDeclaration ] return [qq| class $className(service_type): - +{compileDocstring " " d} __nirum_schema_version__ = \'{SV.toText $ version metadata'}\' __nirum_service_methods__ = \{ {methodMetadata'} @@ -737,13 +799,21 @@ class {className}_Client(client_type, $className): commaNl :: [T.Text] -> T.Text commaNl = T.intercalate ",\n" compileMethod :: Method -> CodeGen Code - compileMethod (Method mName params rtype _etype _anno) = do + compileMethod m@(Method mName params rtype _etype _anno) = do let mName' = toAttributeName' mName params' <- mapM compileMethodParameter $ toList params + let paramDocs = [ T.concat [ ":param " + , toAttributeName' pName + , maybe "" (T.append ": ") $ compileDocs p + -- TODO: types + ] + | p@(Parameter pName _ _) <- toList params + ] rtypeExpr <- compileTypeExpression src rtype ret <- returnCompiler return [qq| def {mName'}(self, {commaNl params'}){ ret rtypeExpr }: +{compileDocstring' " " m paramDocs} raise NotImplementedError('$className has to implement {mName'}()') |] compileMethodParameter :: Parameter -> CodeGen Code @@ -814,11 +884,7 @@ compileModuleBody :: Source -> CodeGen Code compileModuleBody src@Source { sourceModule = boundModule } = do let types' = types boundModule typeCodes <- mapM (compileTypeDeclaration src) $ toList types' - let moduleCode = T.intercalate "\n\n" typeCodes - return [qq| -# TODO: docs -$moduleCode - |] + return $ T.intercalate "\n\n" typeCodes data InstallRequires = InstallRequires { dependencies :: S.Set T.Text @@ -857,6 +923,7 @@ compileModule pythonVersion' source = (Left errMsg, _) -> Left errMsg (Right code, context) -> codeWithDeps context $ [qq|# -*- coding: utf-8 -*- +{compileDocstring "" $ sourceModule source} {imports $ standardImports context} {fromImports $ localImports context} diff --git a/test/Nirum/Constructs/DeclarationSetSpec.hs b/test/Nirum/Constructs/DeclarationSetSpec.hs index 1411f7e..e7a88c4 100644 --- a/test/Nirum/Constructs/DeclarationSetSpec.hs +++ b/test/Nirum/Constructs/DeclarationSetSpec.hs @@ -9,7 +9,7 @@ import Test.Hspec.Meta import Nirum.Constructs (Construct (..)) import qualified Nirum.Constructs.Annotation as A import Nirum.Constructs.Annotation (AnnotationSet) -import Nirum.Constructs.Declaration (Declaration (..)) +import Nirum.Constructs.Declaration (Declaration (..), Documented) import Nirum.Constructs.DeclarationSet ( DeclarationSet , NameDuplication (..) , empty @@ -28,6 +28,8 @@ data SampleDecl = SampleDecl Name AnnotationSet deriving (Eq, Ord, Show) instance Construct SampleDecl where toCode _ = "(do not impl)" +instance Documented SampleDecl + instance Declaration SampleDecl where name (SampleDecl name' _) = name' annotations (SampleDecl _ anno') = anno' diff --git a/test/Nirum/Docs/ReStructuredTextSpec.hs b/test/Nirum/Docs/ReStructuredTextSpec.hs new file mode 100644 index 0000000..5159388 --- /dev/null +++ b/test/Nirum/Docs/ReStructuredTextSpec.hs @@ -0,0 +1,32 @@ +{-# LANGUAGE QuasiQuotes #-} +module Nirum.Docs.ReStructuredTextSpec where + +import Test.Hspec.Meta +import Text.InterpolatedString.Perl6 (q) + +import Nirum.Docs.ReStructuredText (ReStructuredText, render) +import Nirum.DocsSpec (sampleDocument) + +expectedRst :: ReStructuredText +expectedRst = [q|Hello +===== + +Tight list\: + +- List test +- test2 + +Loose list\: + +1. a + +2. b + +A `complex link `_\. +|] + +spec :: Spec +spec = + describe "Docs.ReStructuredText" $ + specify "render" $ + render sampleDocument `shouldBe` expectedRst diff --git a/test/Nirum/ParserSpec.hs b/test/Nirum/ParserSpec.hs index 2974df6..a774cf2 100644 --- a/test/Nirum/ParserSpec.hs +++ b/test/Nirum/ParserSpec.hs @@ -39,7 +39,7 @@ import Nirum.Constructs.Service ( Method (Method) ) import Nirum.Constructs.TypeDeclaration ( EnumMember (EnumMember) , Field (Field, fieldAnnotations) - , Tag (Tag, tagFields) + , Tag (Tag, tagAnnotations, tagFields) , Type (..) , TypeDeclaration (..) ) @@ -714,6 +714,35 @@ union shape } } parse' [s| +union shape + = circle (point origin, offset radius,) + # tag docs + | rectangle (point upper-left, point lower-right,) + | none + ;|] `shouldBeRight` + a { type' = union' + { tags = [ circleTag + { tagAnnotations = singleDocs "tag docs" + } + , rectTag, noneTag + ] + } + } + parse' [s| +union shape + = circle (point origin, offset radius,) + | rectangle (point upper-left, point lower-right,) + | none # tag docs + ;|] `shouldBeRight` + a { type' = union' + { tags = [ circleTag, rectTag + , noneTag + { tagAnnotations = singleDocs "tag docs" + } + ] + } + } + parse' [s| union shape = circle (point origin, @baz offset radius,) | rectangle (point upper-left, @foo ("bar") point lower-right,) diff --git a/test/nirum_fixture/fixture/foo.nrm b/test/nirum_fixture/fixture/foo.nrm index 37e60bf..1415075 100644 --- a/test/nirum_fixture/fixture/foo.nrm +++ b/test/nirum_fixture/fixture/foo.nrm @@ -2,14 +2,19 @@ import fixture.foo.bar (path-unbox, point, int-unbox); import fixture.qux (path, name); unboxed float-unbox (float64); +# Unboxed type docs. + unboxed imported-type-unbox (path-unbox); unboxed way (path); type irum = name; +# Type alias docs. -enum gender = female/yeoseong - | male - ; +enum gender + # Enum docs. + = female/yeoseong + | male + ; enum eva-char = soryu-asuka-langley | ayanami-rei | ikari-shinji @@ -18,11 +23,14 @@ enum eva-char = soryu-asuka-langley ; record point1 ( + # Record docs. bigint left/x, + # Record field docs. bigint top, ); record point2 ( int-unbox left, + # Record field docs. int-unbox top, ); record point3d ( @@ -47,9 +55,14 @@ union mixed-name = western-name ( text first-name ) | culture-agnostic-name (text fullname) ; -union music = pop (text country) - | rnb/rhythm-and-ballad (text country) - ; +union music + # Union docs. + = pop ( text country + # Tag field docs. + ) + # Tag docs. + | rnb/rhythm-and-ballad (text country) + ; union status = run | stop ; @@ -57,5 +70,10 @@ union status = run service null-service (); service ping-service ( - bool ping (text nonce), + # Service docs. + bool ping ( + # Method docs. + text nonce, + # Parameter docs. + ), ); diff --git a/test/python/docs_test.py b/test/python/docs_test.py new file mode 100644 index 0000000..962e35b --- /dev/null +++ b/test/python/docs_test.py @@ -0,0 +1,49 @@ +from fixture.foo import (FloatUnbox, Gender, MixedName, Music, NullService, + PingService, Point1, Point2, Point3d, Pop, Rnb, Way) + + +def test_enum_docs(): + assert Gender.__doc__.strip() == r'Enum docs\.' + + +def test_record_docs(): + assert Point1.__doc__.strip() == r'''Record docs\. + + .. attribute:: left + + Record field docs\. + + .. attribute:: top''' + assert Point2.__doc__.strip() == r'''.. attribute:: left + + Record field docs\. + + .. attribute:: top''' + assert Point3d.__doc__.strip() == r'''.. attribute:: xy + + + .. attribute:: z''' + + +def test_unboxed_type_docs(): + assert FloatUnbox.__doc__.strip() == r'Unboxed type docs\.' + assert Way.__doc__ is None + + +def test_union_docs(): + assert Music.__doc__.strip() == r'Union docs\.' + assert Pop.__doc__.strip() == r'''Tag docs\. + + .. attribute:: country + + Tag field docs\.''' + assert Rnb.__doc__.strip() == r'.. attribute:: country' + assert MixedName.__doc__ is None + + +def test_service_docs(): + assert PingService.__doc__.strip() == r'Service docs\.' + assert PingService.ping.__doc__.strip() == r'''Method docs\. + + :param nonce: Parameter docs\.''' + assert NullService.__doc__ is None