{-# LANGUAGE OverloadedStrings #-}
module HsLua.Packaging.Documentation
( documentation
, getdocumentation
, registerDocumentation
, pushModuleDoc
, pushFunctionDoc
, pushFieldDoc
, docsField
) where
import Data.Version (showVersion)
import HsLua.Core as Lua
import HsLua.Marshalling
import HsLua.Packaging.Types
documentation :: LuaError e => DocumentedFunction e
documentation :: DocumentedFunction e
documentation =
DocumentedFunction :: forall e.
LuaE e NumResults -> Name -> FunctionDoc -> DocumentedFunction e
DocumentedFunction
{ callFunction :: LuaE e NumResults
callFunction = LuaE e NumResults
forall e. LuaError e => LuaE e NumResults
documentationHaskellFunction
, functionName :: Name
functionName = Name
"documentation"
, functionDoc :: FunctionDoc
functionDoc = FunctionDoc :: Text
-> [ParameterDoc] -> ResultsDoc -> Maybe Version -> FunctionDoc
FunctionDoc
{ functionDescription :: Text
functionDescription =
Text
"Retrieves the documentation of the given object."
, parameterDocs :: [ParameterDoc]
parameterDocs =
[ ParameterDoc :: Text -> Text -> Text -> Bool -> ParameterDoc
ParameterDoc
{ parameterName :: Text
parameterName = Text
"value"
, parameterType :: Text
parameterType = Text
"any"
, parameterDescription :: Text
parameterDescription = Text
"documented object"
, parameterIsOptional :: Bool
parameterIsOptional = Bool
False
}
]
, functionResultsDocs :: ResultsDoc
functionResultsDocs = [ResultValueDoc] -> ResultsDoc
ResultsDocList
[ Text -> Text -> ResultValueDoc
ResultValueDoc Text
"string|nil" Text
"docstring" ]
, functionSince :: Maybe Version
functionSince = Maybe Version
forall a. Maybe a
Nothing
}
}
documentationHaskellFunction :: LuaError e => LuaE e NumResults
documentationHaskellFunction :: LuaE e NumResults
documentationHaskellFunction = StackIndex -> LuaE e Bool
forall e. StackIndex -> LuaE e Bool
isnoneornil (CInt -> StackIndex
nthBottom CInt
1) LuaE e Bool -> (Bool -> LuaE e NumResults) -> LuaE e NumResults
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> String -> LuaE e NumResults
forall e a. LuaError e => String -> LuaE e a
failLua String
"expected a non-nil value as argument 1"
Bool
_ -> CInt -> NumResults
NumResults CInt
1 NumResults -> LuaE e Type -> LuaE e NumResults
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ StackIndex -> LuaE e Type
forall e. LuaError e => StackIndex -> LuaE e Type
getdocumentation StackIndex
top
getdocumentation :: LuaError e => StackIndex -> LuaE e Lua.Type
getdocumentation :: StackIndex -> LuaE e Type
getdocumentation StackIndex
idx = do
StackIndex
idx' <- StackIndex -> LuaE e StackIndex
forall e. StackIndex -> LuaE e StackIndex
absindex StackIndex
idx
LuaE e ()
forall e. LuaError e => LuaE e ()
pushDocumentationTable
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
pushvalue StackIndex
idx'
StackIndex -> LuaE e Type
forall e. LuaError e => StackIndex -> LuaE e Type
rawget (CInt -> StackIndex
nth CInt
2) LuaE e Type -> LuaE e () -> LuaE e Type
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
Lua.remove (CInt -> StackIndex
nth CInt
2)
registerDocumentation :: LuaError e
=> StackIndex
-> LuaE e ()
registerDocumentation :: StackIndex -> LuaE e ()
registerDocumentation StackIndex
idx = do
Int -> String -> LuaE e ()
forall e. LuaError e => Int -> String -> LuaE e ()
checkstack' Int
10 String
"registerDocumentation"
StackIndex
idx' <- StackIndex -> LuaE e StackIndex
forall e. StackIndex -> LuaE e StackIndex
absindex StackIndex
idx
LuaE e ()
forall e. LuaError e => LuaE e ()
pushDocumentationTable
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
pushvalue StackIndex
idx'
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
pushvalue (CInt -> StackIndex
nth CInt
3)
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
rawset (CInt -> StackIndex
nth CInt
3)
Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
2
pushDocumentationTable :: LuaError e => LuaE e ()
pushDocumentationTable :: LuaE e ()
pushDocumentationTable = StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
Lua.getfield StackIndex
registryindex Name
docsField LuaE e Type -> (Type -> LuaE e ()) -> LuaE e ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Type
Lua.TypeTable -> () -> LuaE e ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Type
_ -> do
Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
1
LuaE e ()
forall e. LuaE e ()
newtable
ByteString -> LuaE e ()
forall e. ByteString -> LuaE e ()
pushstring ByteString
"k"
StackIndex -> Name -> LuaE e ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield (CInt -> StackIndex
nth CInt
2) Name
"__mode"
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
pushvalue StackIndex
top
StackIndex -> Name -> LuaE e ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield StackIndex
registryindex Name
docsField
docsField :: Name
docsField :: Name
docsField = Name
"HsLua docs"
pushModuleDoc :: LuaError e => Pusher e (Module e)
pushModuleDoc :: Pusher e (Module e)
pushModuleDoc = [(Name, Pusher e (Module e))] -> Pusher e (Module e)
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable
[ (Name
"name", Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName (Name -> LuaE e ()) -> (Module e -> Name) -> Pusher e (Module e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module e -> Name
forall e. Module e -> Name
moduleName)
, (Name
"description", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (Module e -> Text) -> Pusher e (Module e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module e -> Text
forall e. Module e -> Text
moduleDescription)
, (Name
"fields", Pusher e (Field e) -> [Field e] -> LuaE e ()
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushList Pusher e (Field e)
forall e. LuaError e => Pusher e (Field e)
pushFieldDoc ([Field e] -> LuaE e ())
-> (Module e -> [Field e]) -> Pusher e (Module e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module e -> [Field e]
forall e. Module e -> [Field e]
moduleFields)
, (Name
"functions", Pusher e (DocumentedFunction e)
-> [DocumentedFunction e] -> LuaE e ()
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushList Pusher e (DocumentedFunction e)
forall e. LuaError e => Pusher e (DocumentedFunction e)
pushFunctionDoc ([DocumentedFunction e] -> LuaE e ())
-> (Module e -> [DocumentedFunction e]) -> Pusher e (Module e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module e -> [DocumentedFunction e]
forall e. Module e -> [DocumentedFunction e]
moduleFunctions)
]
pushFieldDoc :: LuaError e => Pusher e (Field e)
pushFieldDoc :: Pusher e (Field e)
pushFieldDoc = [(Name, Pusher e (Field e))] -> Pusher e (Field e)
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable
[ (Name
"name", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (Field e -> Text) -> Pusher e (Field e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field e -> Text
forall e. Field e -> Text
fieldName)
, (Name
"description", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (Field e -> Text) -> Pusher e (Field e)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field e -> Text
forall e. Field e -> Text
fieldDescription)
]
pushFunctionDoc :: LuaError e => Pusher e (DocumentedFunction e)
pushFunctionDoc :: Pusher e (DocumentedFunction e)
pushFunctionDoc DocumentedFunction e
fun = [(Name, FunctionDoc -> LuaE e ())] -> FunctionDoc -> LuaE e ()
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable
[ (Name
"name", Name -> LuaE e ()
forall e. Name -> LuaE e ()
pushName (Name -> LuaE e ())
-> (FunctionDoc -> Name) -> FunctionDoc -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> FunctionDoc -> Name
forall a b. a -> b -> a
const (DocumentedFunction e -> Name
forall e. DocumentedFunction e -> Name
functionName DocumentedFunction e
fun))
, (Name
"description", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (FunctionDoc -> Text) -> FunctionDoc -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionDoc -> Text
functionDescription)
, (Name
"parameters", Pusher e ParameterDoc -> [ParameterDoc] -> LuaE e ()
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushList Pusher e ParameterDoc
forall e. LuaError e => Pusher e ParameterDoc
pushParameterDoc ([ParameterDoc] -> LuaE e ())
-> (FunctionDoc -> [ParameterDoc]) -> FunctionDoc -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionDoc -> [ParameterDoc]
parameterDocs)
, (Name
"results", Pusher e ResultsDoc
forall e. LuaError e => Pusher e ResultsDoc
pushResultsDoc Pusher e ResultsDoc
-> (FunctionDoc -> ResultsDoc) -> FunctionDoc -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionDoc -> ResultsDoc
functionResultsDocs)
, (Name
"since", LuaE e () -> (Version -> LuaE e ()) -> Maybe Version -> LuaE e ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe LuaE e ()
forall e. LuaE e ()
pushnil (String -> LuaE e ()
forall e. String -> LuaE e ()
pushString (String -> LuaE e ())
-> (Version -> String) -> Version -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
showVersion) (Maybe Version -> LuaE e ())
-> (FunctionDoc -> Maybe Version) -> FunctionDoc -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunctionDoc -> Maybe Version
functionSince)
] (DocumentedFunction e -> FunctionDoc
forall e. DocumentedFunction e -> FunctionDoc
functionDoc DocumentedFunction e
fun)
pushParameterDoc :: LuaError e => Pusher e ParameterDoc
pushParameterDoc :: Pusher e ParameterDoc
pushParameterDoc = [(Name, Pusher e ParameterDoc)] -> Pusher e ParameterDoc
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable
[ (Name
"name", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (ParameterDoc -> Text) -> Pusher e ParameterDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterDoc -> Text
parameterName)
, (Name
"type", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (ParameterDoc -> Text) -> Pusher e ParameterDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterDoc -> Text
parameterType)
, (Name
"description", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text -> (ParameterDoc -> Text) -> Pusher e ParameterDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterDoc -> Text
parameterDescription)
, (Name
"optional", Pusher e Bool
forall e. Pusher e Bool
pushBool Pusher e Bool -> (ParameterDoc -> Bool) -> Pusher e ParameterDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParameterDoc -> Bool
parameterIsOptional)
]
pushResultsDoc :: LuaError e => Pusher e ResultsDoc
pushResultsDoc :: Pusher e ResultsDoc
pushResultsDoc = \case
ResultsDocMult Text
desc -> Pusher e Text
forall e. Pusher e Text
pushText Text
desc
ResultsDocList [ResultValueDoc]
resultDocs -> Pusher e ResultValueDoc -> [ResultValueDoc] -> LuaE e ()
forall e a. LuaError e => Pusher e a -> [a] -> LuaE e ()
pushList Pusher e ResultValueDoc
forall e. LuaError e => Pusher e ResultValueDoc
pushResultValueDoc [ResultValueDoc]
resultDocs
pushResultValueDoc :: LuaError e => Pusher e ResultValueDoc
pushResultValueDoc :: Pusher e ResultValueDoc
pushResultValueDoc = [(Name, Pusher e ResultValueDoc)] -> Pusher e ResultValueDoc
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable
[ (Name
"type", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text
-> (ResultValueDoc -> Text) -> Pusher e ResultValueDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ResultValueDoc -> Text
resultValueType)
, (Name
"description", Pusher e Text
forall e. Pusher e Text
pushText Pusher e Text
-> (ResultValueDoc -> Text) -> Pusher e ResultValueDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ResultValueDoc -> Text
resultValueDescription)
]