module Clang.Internal.Comment
( ParsedComment(..)
, ParamPassDirection(..)
, parseComment
, getFFIComment
) where
import Control.Monad
import Control.Monad.IO.Class
import Data.Typeable
import qualified Clang.Internal.FFI as FFI
import Clang.Internal.Monad
data ParsedComment s
= TextComment (FFI.Comment s) (FFI.ClangString s)
| InlineCommandComment (FFI.Comment s) (FFI.ClangString s) FFI.InlineCommandRenderStyle [FFI.ClangString s]
| HTMLStartTagComment (FFI.Comment s) (FFI.ClangString s) [(FFI.ClangString s, FFI.ClangString s)] Bool
| HTMLEndTagComment (FFI.Comment s) (FFI.ClangString s)
| ParagraphComment (FFI.Comment s)
| BlockCommandComment (FFI.Comment s) (FFI.ClangString s) [FFI.ClangString s] (Maybe (ParsedComment s))
| ParamCommandComment (FFI.Comment s) (FFI.ClangString s) (Maybe Int) ParamPassDirection
| TypeParamCommandComment (FFI.Comment s) (FFI.ClangString s) (Maybe [Int])
| VerbatimBlockCommandComment (FFI.Comment s) (Maybe (ParsedComment s))
| VerbatimBlockLineComment (FFI.Comment s) (FFI.ClangString s)
| VerbatimLineComment (FFI.Comment s) (FFI.ClangString s)
| FullComment (FFI.Comment s)
deriving (Eq, Ord, Typeable)
data ParamPassDirection
= ExplicitParamPassDirection FFI.ParamPassDirectionKind
| InferredParamPassDirection FFI.ParamPassDirectionKind
deriving (Eq, Ord, Read, Show, Typeable)
parseComment :: ClangBase m => FFI.Comment s -> ClangT s m (Maybe (ParsedComment s))
parseComment c = do
kind <- liftIO $ FFI.comment_getKind c
case kind of
FFI.NullComment -> pure Nothing
FFI.TextComment -> Just . TextComment c <$> FFI.textComment_getText c
FFI.InlineCommandComment -> do v <- InlineCommandComment c <$> FFI.inlineCommandComment_getCommandName c
<*> inlineCommandComment_getRenderKind c
<*> inlineCommandComment_getArgs c
return $ Just v
FFI.HTMLStartTagComment -> do v <- HTMLStartTagComment c <$> FFI.hTMLTagComment_getTagName c
<*> htmlStartTagComment_getAttrs c
<*> htmlStartTagComment_isSelfClosing c
return $ Just v
FFI.HTMLEndTagComment -> Just . HTMLEndTagComment c <$> FFI.hTMLTagComment_getTagName c
FFI.ParagraphComment -> pure $ Just (ParagraphComment c)
FFI.BlockCommandComment -> do v <- BlockCommandComment c <$> FFI.blockCommandComment_getCommandName c
<*> blockCommandComment_getArgs c
<*> blockCommandComment_getParagraph c
return $ Just v
FFI.ParamCommandComment -> do v <- ParamCommandComment c <$> FFI.paramCommandComment_getParamName c
<*> paramCommandComment_getParamIndex c
<*> paramCommandComment_getDirection c
return $ Just v
FFI.TParamCommandComment -> do v <- TypeParamCommandComment c
<$> FFI.tParamCommandComment_getParamName c
<*> tParamCommandComment_getPosition c
return $ Just v
FFI.VerbatimBlockCommandComment -> Just . VerbatimBlockCommandComment c <$> blockCommandComment_getParagraph c
FFI.VerbatimBlockLineComment -> Just . VerbatimBlockLineComment c <$> FFI.verbatimBlockLineComment_getText c
FFI.VerbatimLineComment -> Just . VerbatimLineComment c <$> FFI.verbatimLineComment_getText c
FFI.FullComment -> pure $ Just (FullComment c)
getFFIComment :: ParsedComment s -> FFI.Comment s
getFFIComment (TextComment c _) = c
getFFIComment (InlineCommandComment c _ _ _) = c
getFFIComment (HTMLStartTagComment c _ _ _) = c
getFFIComment (HTMLEndTagComment c _) = c
getFFIComment (ParagraphComment c) = c
getFFIComment (BlockCommandComment c _ _ _) = c
getFFIComment (ParamCommandComment c _ _ _) = c
getFFIComment (TypeParamCommandComment c _ _) = c
getFFIComment (VerbatimBlockCommandComment c _) = c
getFFIComment (VerbatimBlockLineComment c _) = c
getFFIComment (VerbatimLineComment c _) = c
getFFIComment (FullComment c) = c
inlineCommandComment_getRenderKind :: ClangBase m => FFI.Comment s'
-> ClangT s m FFI.InlineCommandRenderStyle
inlineCommandComment_getRenderKind c = liftIO $ FFI.inlineCommandComment_getRenderKind c
inlineCommandComment_getArgs :: ClangBase m => FFI.Comment s' -> ClangT s m [FFI.ClangString s]
inlineCommandComment_getArgs c = do
numArgs <- liftIO $ FFI.inlineCommandComment_getNumArgs c
mapM (FFI.inlineCommandComment_getArgText c) [0..(numArgs 1)]
htmlStartTagComment_getAttrs :: ClangBase m => FFI.Comment s'
-> ClangT s m [(FFI.ClangString s, FFI.ClangString s)]
htmlStartTagComment_getAttrs c = do
numAttrs <- liftIO $ FFI.hTMLStartTag_getNumAttrs c
forM [0..numAttrs] $ \attr -> do
attrName <- FFI.hTMLStartTag_getAttrName c attr
attrValue <- FFI.hTMLStartTag_getAttrValue c attr
return (attrName, attrValue)
htmlStartTagComment_isSelfClosing :: ClangBase m => FFI.Comment s' -> ClangT s m Bool
htmlStartTagComment_isSelfClosing c = liftIO $ FFI.hTMLStartTagComment_isSelfClosing c
blockCommandComment_getArgs :: ClangBase m => FFI.Comment s' -> ClangT s m [FFI.ClangString s]
blockCommandComment_getArgs c = do
numArgs <- liftIO $ FFI.blockCommandComment_getNumArgs c
mapM (FFI.blockCommandComment_getArgText c) [0..(numArgs 1)]
blockCommandComment_getParagraph :: ClangBase m => FFI.Comment s' -> ClangT s m (Maybe (ParsedComment s))
blockCommandComment_getParagraph c =
parseComment =<< liftIO (FFI.blockCommandComment_getParagraph mkProxy c)
paramCommandComment_getParamIndex :: ClangBase m => FFI.Comment s' -> ClangT s m (Maybe Int)
paramCommandComment_getParamIndex c = do
valid <- liftIO $ FFI.paramCommandComment_isParamIndexValid c
if valid
then Just <$> (liftIO $ FFI.paramCommandComment_getParamIndex c)
else return Nothing
paramCommandComment_getDirection :: ClangBase m => FFI.Comment s' -> ClangT s m ParamPassDirection
paramCommandComment_getDirection c = do
dir <- liftIO $ FFI.paramCommandComment_getDirection c
explicit <- liftIO $ FFI.paramCommandComment_isDirectionExplicit c
return $ if explicit
then ExplicitParamPassDirection dir
else InferredParamPassDirection dir
tParamCommandComment_getPosition :: ClangBase m => FFI.Comment s' -> ClangT s m (Maybe [Int])
tParamCommandComment_getPosition c = do
valid <- liftIO $ FFI.tParamCommandComment_isParamPositionValid c
if valid
then do depth <- liftIO $ FFI.tParamCommandComment_getDepth c
indices <- forM [0..depth] $ \d ->
liftIO $ FFI.tParamCommandComment_getIndex c d
return $ Just indices
else return Nothing