License | BSD3 |
---|---|
Maintainer | The Idris Community. |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Docstring a = DocString Options (Blocks a)
- data Block a
- data Inline a
- parseDocstring :: Text -> Docstring ()
- renderDocstring :: (a -> String -> Doc OutputAnnotation) -> Docstring a -> Doc OutputAnnotation
- emptyDocstring :: Docstring a
- nullDocstring :: Docstring a -> Bool
- noDocs :: (Docstring a, [(Name, Docstring a)])
- overview :: Docstring a -> Docstring a
- containsText :: Text -> Docstring a -> Bool
- renderHtml :: Docstring DocTerm -> Html
- annotCode :: forall a b. (String -> b) -> Docstring a -> Docstring b
- data DocTerm
- renderDocTerm :: (Term -> Doc OutputAnnotation) -> (Term -> Term) -> DocTerm -> String -> Doc OutputAnnotation
- checkDocstring :: forall a b. (String -> [String] -> String -> a -> b) -> Docstring a -> Docstring b
Documentation
Representation of Idris's inline documentation. The type paramter represents the type of terms that are associated with code blocks.
Instances
Functor Docstring Source # | |
Foldable Docstring Source # | |
Defined in Idris.Docstrings fold :: Monoid m => Docstring m -> m # foldMap :: Monoid m => (a -> m) -> Docstring a -> m # foldr :: (a -> b -> b) -> b -> Docstring a -> b # foldr' :: (a -> b -> b) -> b -> Docstring a -> b # foldl :: (b -> a -> b) -> b -> Docstring a -> b # foldl' :: (b -> a -> b) -> b -> Docstring a -> b # foldr1 :: (a -> a -> a) -> Docstring a -> a # foldl1 :: (a -> a -> a) -> Docstring a -> a # toList :: Docstring a -> [a] # length :: Docstring a -> Int # elem :: Eq a => a -> Docstring a -> Bool # maximum :: Ord a => Docstring a -> a # minimum :: Ord a => Docstring a -> a # | |
Traversable Docstring Source # | |
Show a => Show (Docstring a) Source # | |
Generic (Docstring a) Source # | |
Binary a => Binary (Docstring a) Source # | |
NFData a => NFData (Docstring a) Source # | |
Defined in Idris.DeepSeq | |
type Rep (Docstring a) Source # | |
Defined in Idris.Docstrings |
Block-level elements.
Para (Inlines a) | |
Header Int (Inlines a) | |
Blockquote (Blocks a) | |
List Bool ListType [Blocks a] | |
CodeBlock CodeAttr Text a | |
HtmlBlock Text | |
HRule |
Instances
Functor Block Source # | |
Foldable Block Source # | |
Defined in Idris.Docstrings fold :: Monoid m => Block m -> m # foldMap :: Monoid m => (a -> m) -> Block a -> m # foldr :: (a -> b -> b) -> b -> Block a -> b # foldr' :: (a -> b -> b) -> b -> Block a -> b # foldl :: (b -> a -> b) -> b -> Block a -> b # foldl' :: (b -> a -> b) -> b -> Block a -> b # foldr1 :: (a -> a -> a) -> Block a -> a # foldl1 :: (a -> a -> a) -> Block a -> a # elem :: Eq a => a -> Block a -> Bool # maximum :: Ord a => Block a -> a # minimum :: Ord a => Block a -> a # | |
Traversable Block Source # | |
Show a => Show (Block a) Source # | |
Generic (Block a) Source # | |
Binary a => Binary (Block a) Source # | |
NFData a => NFData (Block a) Source # | |
Defined in Idris.DeepSeq | |
type Rep (Block a) Source # | |
Defined in Idris.Docstrings |
Str Text | |
Space | |
SoftBreak | |
LineBreak | |
Emph (Inlines a) | |
Strong (Inlines a) | |
Code Text a | |
Link (Inlines a) Text Text | |
Image (Inlines a) Text Text | |
Entity Text | |
RawHtml Text |
Instances
Functor Inline Source # | |
Foldable Inline Source # | |
Defined in Idris.Docstrings fold :: Monoid m => Inline m -> m # foldMap :: Monoid m => (a -> m) -> Inline a -> m # foldr :: (a -> b -> b) -> b -> Inline a -> b # foldr' :: (a -> b -> b) -> b -> Inline a -> b # foldl :: (b -> a -> b) -> b -> Inline a -> b # foldl' :: (b -> a -> b) -> b -> Inline a -> b # foldr1 :: (a -> a -> a) -> Inline a -> a # foldl1 :: (a -> a -> a) -> Inline a -> a # elem :: Eq a => a -> Inline a -> Bool # maximum :: Ord a => Inline a -> a # minimum :: Ord a => Inline a -> a # | |
Traversable Inline Source # | |
Show a => Show (Inline a) Source # | |
Generic (Inline a) Source # | |
Binary a => Binary (Inline a) Source # | |
NFData a => NFData (Inline a) Source # | |
Defined in Idris.DeepSeq | |
type Rep (Inline a) Source # | |
Defined in Idris.Docstrings |
parseDocstring :: Text -> Docstring () Source #
Construct a docstring from a Text that contains Markdown-formatted docs
renderDocstring :: (a -> String -> Doc OutputAnnotation) -> Docstring a -> Doc OutputAnnotation Source #
Convert a docstring to be shown by the pretty-printer
emptyDocstring :: Docstring a Source #
The empty docstring
nullDocstring :: Docstring a -> Bool Source #
Check whether a docstring is emtpy
overview :: Docstring a -> Docstring a Source #
Construct a docstring consisting of the first block-level element of the argument docstring, for use in summaries.
Annotate the code samples in a docstring
The various kinds of code samples that can be embedded in docs
Instances
Show DocTerm Source # | |
Generic DocTerm Source # | |
Binary DocTerm Source # | |
NFData DocTerm Source # | |
Defined in Idris.DeepSeq | |
type Rep DocTerm Source # | |
Defined in Idris.Docstrings type Rep DocTerm = D1 (MetaData "DocTerm" "Idris.Docstrings" "idris-1.3.2-3LpOXLFJmzJ3DT7fAtaO1v" False) ((C1 (MetaCons "Unchecked" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Checked" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Term))) :+: (C1 (MetaCons "Example" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Term)) :+: C1 (MetaCons "Failing" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Err)))) |
renderDocTerm :: (Term -> Doc OutputAnnotation) -> (Term -> Term) -> DocTerm -> String -> Doc OutputAnnotation Source #
Render a term in the documentation