{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
Module      : HsLua.Packaging.Rendering
Copyright   : © 2020-2022 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb+hslua@zeitkraut.de>
Stability   : alpha
Portability : Portable

Render function and module documentation.
-}
module HsLua.Packaging.Rendering
  {-# DEPRECATED "Use getdocumentation with a custom renderer." #-}
  ( -- * Documentation
    render
  , renderModule
  , renderFunction
  ) where

import Data.Text (Text)
import Data.Version (showVersion)
import HsLua.Core
import HsLua.Packaging.Types
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified HsLua.Core.Utf8 as Utf8

#if !MIN_VERSION_base(4,12,0)
import Data.Semigroup (Semigroup ((<>)))
#endif

--
-- Module documentation
--

-- | Alias for 'renderModule'.
render :: Module e -> Text
render :: Module e -> Text
render = Module e -> Text
forall e. Module e -> Text
renderModule

-- | Renders module documentation as Markdown.
renderModule :: Module e -> Text
renderModule :: Module e -> Text
renderModule Module e
mdl =
  let fields :: [Field e]
fields = Module e -> [Field e]
forall e. Module e -> [Field e]
moduleFields Module e
mdl
  in [Text] -> Text
T.unlines
     [ Text
"# " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ByteString -> Text
T.decodeUtf8 (Name -> ByteString
fromName (Name -> ByteString) -> Name -> ByteString
forall a b. (a -> b) -> a -> b
$ Module e -> Name
forall e. Module e -> Name
moduleName Module e
mdl)
     , Text
""
     , Module e -> Text
forall e. Module e -> Text
moduleDescription Module e
mdl
     , [Field e] -> Text
forall e. [Field e] -> Text
renderFields [Field e]
fields
     , [DocumentedFunction e] -> Text
forall e. [DocumentedFunction e] -> Text
renderFunctions (Module e -> [DocumentedFunction e]
forall e. Module e -> [DocumentedFunction e]
moduleFunctions Module e
mdl)
     ]

-- | Renders the full function documentation section.
renderFunctions :: [DocumentedFunction e] -> Text
renderFunctions :: [DocumentedFunction e] -> Text
renderFunctions = \case
  [] -> Text
forall a. Monoid a => a
mempty
  [DocumentedFunction e]
fs -> Text
"\n## Functions\n\n"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"\n\n" ((DocumentedFunction e -> Text) -> [DocumentedFunction e] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((Text
"### " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text)
-> (DocumentedFunction e -> Text) -> DocumentedFunction e -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DocumentedFunction e -> Text
forall e. DocumentedFunction e -> Text
renderFunction) [DocumentedFunction e]
fs)

-- | Renders documentation of a function.
renderFunction :: DocumentedFunction e  -- ^ function
               -> Text                  -- ^ function docs
renderFunction :: DocumentedFunction e -> Text
renderFunction DocumentedFunction e
fn =
  let fnDoc :: FunctionDoc
fnDoc = DocumentedFunction e -> FunctionDoc
forall e. DocumentedFunction e -> FunctionDoc
functionDoc DocumentedFunction e
fn
      fnName :: Text
fnName = ByteString -> Text
Utf8.toText (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Name -> ByteString
fromName (DocumentedFunction e -> Name
forall e. DocumentedFunction e -> Name
functionName DocumentedFunction e
fn)
      name :: Text
name = if Text -> Bool
T.null Text
fnName
             then Text
"<anonymous function>"
             else Text
fnName
  in Text -> [Text] -> Text
T.intercalate Text
"\n"
     [ Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FunctionDoc -> Text
renderFunctionParams FunctionDoc
fnDoc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
     , Text
""
     , FunctionDoc -> Text
renderFunctionDoc FunctionDoc
fnDoc
     ]

-- | Renders the parameter names of a function, separated by commas.
renderFunctionParams :: FunctionDoc -> Text
renderFunctionParams :: FunctionDoc -> Text
renderFunctionParams FunctionDoc
fd =
    Text -> [Text] -> Text
T.intercalate Text
", "
  ([Text] -> Text)
-> ([ParameterDoc] -> [Text]) -> [ParameterDoc] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ParameterDoc -> Text) -> [ParameterDoc] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ParameterDoc -> Text
parameterName
  ([ParameterDoc] -> Text) -> [ParameterDoc] -> Text
forall a b. (a -> b) -> a -> b
$ FunctionDoc -> [ParameterDoc]
parameterDocs FunctionDoc
fd

-- | Render documentation for fields as Markdown.
renderFields :: [Field e] -> Text
renderFields :: [Field e] -> Text
renderFields [Field e]
fs =
  if [Field e] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Field e]
fs
  then Text
forall a. Monoid a => a
mempty
  else [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
       [ Text
"\n"
       , Text -> [Text] -> Text
T.intercalate Text
"\n\n" ((Field e -> Text) -> [Field e] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((Text
"### " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Field e -> Text) -> Field e -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field e -> Text
forall e. Field e -> Text
renderField) [Field e]
fs)
       ]

-- | Renders documentation for a single field.
renderField :: Field e -> Text
renderField :: Field e -> Text
renderField Field e
f = Field e -> Text
forall e. Field e -> Text
fieldName Field e
f Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Field e -> Text
forall e. Field e -> Text
fieldDescription Field e
f

--
-- Function documentation
--

-- | Renders the documentation of a function as Markdown.
renderFunctionDoc :: FunctionDoc -> Text
renderFunctionDoc :: FunctionDoc -> Text
renderFunctionDoc (FunctionDoc Text
desc [ParameterDoc]
paramDocs ResultsDoc
resultDoc Maybe Version
mVersion) =
  let sinceTag :: Text
sinceTag = case Maybe Version
mVersion of
        Maybe Version
Nothing -> Text
forall a. Monoid a => a
mempty
        Just Version
version -> String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"\n\n*Since: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
version String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"*"
  in (if Text -> Bool
T.null Text
desc
      then Text
""
      else Text
desc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
sinceTag Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n\n") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
     [ParameterDoc] -> Text
renderParamDocs [ParameterDoc]
paramDocs Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
     ResultsDoc -> Text
renderResultsDoc ResultsDoc
resultDoc

-- | Renders function parameter documentation as a Markdown blocks.
renderParamDocs :: [ParameterDoc] -> Text
renderParamDocs :: [ParameterDoc] -> Text
renderParamDocs [ParameterDoc]
pds = Text
"Parameters:\n\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
  Text -> [Text] -> Text
T.intercalate Text
"\n" ((ParameterDoc -> Text) -> [ParameterDoc] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ParameterDoc -> Text
renderParamDoc [ParameterDoc]
pds)

-- | Renders the documentation of a function parameter as a Markdown
-- line.
renderParamDoc :: ParameterDoc -> Text
renderParamDoc :: ParameterDoc -> Text
renderParamDoc ParameterDoc
pd = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
  [ ParameterDoc -> Text
parameterName ParameterDoc
pd
  ,  Text
"\n:   "
  , ParameterDoc -> Text
parameterDescription ParameterDoc
pd
  , Text
" (", ParameterDoc -> Text
parameterType ParameterDoc
pd, Text
")\n"
  ]

-- | Renders the documentation of a function result as a Markdown list
-- item.
renderResultsDoc :: ResultsDoc -> Text
renderResultsDoc :: ResultsDoc -> Text
renderResultsDoc = \case
  ResultsDocList []  -> Text
forall a. Monoid a => a
mempty
  ResultsDocList [ResultValueDoc]
rds ->
    Text
"\nReturns:\n\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"\n" ((ResultValueDoc -> Text) -> [ResultValueDoc] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ResultValueDoc -> Text
renderResultValueDoc [ResultValueDoc]
rds)
  ResultsDocMult Text
txt -> Text
" -  " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
indent Int
4 Text
txt

-- | Renders the documentation of a function result as a Markdown list
-- item.
renderResultValueDoc :: ResultValueDoc -> Text
renderResultValueDoc :: ResultValueDoc -> Text
renderResultValueDoc ResultValueDoc
rd = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
  [ Text
" -  "
  , ResultValueDoc -> Text
resultValueDescription ResultValueDoc
rd
  , Text
" (", ResultValueDoc -> Text
resultValueType ResultValueDoc
rd, Text
")"
  ]

indent :: Int -> Text -> Text
indent :: Int -> Text -> Text
indent Int
n = Text -> Text -> Text -> Text
T.replace Text
"\n" (Int -> Text -> Text
T.replicate Int
n Text
" ")