-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Handle Jira wiki markup
--
-- Parse jira wiki text into an abstract syntax tree for easy
-- transformation to other formats.
@package jira-wiki-markup
@version 1.5.1
-- | Jira markup types.
module Text.Jira.Markup
-- | Jira document
newtype Doc
Doc :: [Block] -> Doc
[fromDoc] :: Doc -> [Block]
-- | Blocks of text.
data Block
-- | Code block with panel parameters
Code :: Language -> [Parameter] -> Text -> Block
-- | text displayed in a specific color
Color :: ColorName -> [Block] -> Block
-- | Block of quoted content
BlockQuote :: [Block] -> Block
-- | Header with level and text
Header :: Int -> [Inline] -> Block
-- | horizontal ruler
HorizontalRule :: Block
-- | List
List :: ListStyle -> [[Block]] -> Block
-- | Unformatted text
NoFormat :: [Parameter] -> Text -> Block
-- | Formatted panel
Panel :: [Parameter] -> [Block] -> Block
-- | Paragraph of text
Para :: [Inline] -> Block
-- | Table
Table :: [Row] -> Block
-- | Inline Jira markup elements.
data Inline
-- | anchor for internal links
Anchor :: Text -> Inline
-- | URL which is also a link
AutoLink :: URL -> Inline
-- | source of a citation
Citation :: [Inline] -> Inline
-- | colored inline text
ColorInline :: ColorName -> [Inline] -> Inline
-- | emoticon
Emoji :: Icon -> Inline
-- | named or numeric HTML entity
Entity :: Text -> Inline
-- | an image
Image :: [Parameter] -> URL -> Inline
-- | hard linebreak
Linebreak :: Inline
-- | hyperlink with alias
Link :: LinkType -> [Inline] -> URL -> Inline
-- | text rendered with monospaced font
Monospaced :: [Inline] -> Inline
-- | space between words
Space :: Inline
-- | single char with special meaning
SpecialChar :: Char -> Inline
-- | simple, markup-less string
Str :: Text -> Inline
-- | styled text
Styled :: InlineStyle -> [Inline] -> Inline
-- | Supported inline text effect styles.
data InlineStyle
-- | emphasized text
Emphasis :: InlineStyle
-- | text marked as having been inserted
Insert :: InlineStyle
-- | deleted (struk-out) text
Strikeout :: InlineStyle
-- | strongly emphasized text
Strong :: InlineStyle
-- | subscript text
Subscript :: InlineStyle
-- | superscript text
Superscript :: InlineStyle
-- | Type of a link.
data LinkType
-- | link to an attachment
Attachment :: LinkType
-- | link to an email address
Email :: LinkType
-- | external resource, like a website
External :: LinkType
-- | smart-card link (external)
SmartCard :: LinkType
-- | "smart" link with icon, short-name
SmartLink :: LinkType
-- | link to a user
User :: LinkType
-- | Style used for list items.
data ListStyle
-- | List with round bullets
CircleBullets :: ListStyle
-- | List with square bullets
SquareBullets :: ListStyle
-- | Enumeration, i.e., numbered items
Enumeration :: ListStyle
-- | Unified resource location
newtype URL
URL :: Text -> URL
[fromURL] :: URL -> Text
-- | Text color
newtype ColorName
ColorName :: Text -> ColorName
-- | Graphical emoticons
data Icon
IconSlightlySmiling :: Icon
IconFrowning :: Icon
IconTongue :: Icon
IconSmiling :: Icon
IconWinking :: Icon
IconThumbsUp :: Icon
IconThumbsDown :: Icon
IconInfo :: Icon
IconCheckmark :: Icon
IconX :: Icon
IconAttention :: Icon
IconPlus :: Icon
IconMinus :: Icon
IconQuestionmark :: Icon
IconOn :: Icon
IconOff :: Icon
IconStar :: Icon
IconStarRed :: Icon
IconStarGreen :: Icon
IconStarBlue :: Icon
IconStarYellow :: Icon
IconFlag :: Icon
IconFlagOff :: Icon
-- | Table row, containing an arbitrary number of cells.
newtype Row
Row :: [Cell] -> Row
[fromRow] :: Row -> [Cell]
-- | Table cell with block content
data Cell
BodyCell :: [Block] -> Cell
HeaderCell :: [Block] -> Cell
-- | Programming language used for syntax highlighting.
newtype Language
Language :: Text -> Language
-- | Panel parameter
data Parameter
Parameter :: Text -> Text -> Parameter
[parameterKey] :: Parameter -> Text
[parameterValue] :: Parameter -> Text
-- | Normalize a list of inlines, merging elements where possible.
normalizeInlines :: [Inline] -> [Inline]
-- | Gets the characters used to represent an emoji.
iconText :: Icon -> Text
instance GHC.Show.Show Text.Jira.Markup.InlineStyle
instance GHC.Classes.Ord Text.Jira.Markup.InlineStyle
instance GHC.Classes.Eq Text.Jira.Markup.InlineStyle
instance GHC.Show.Show Text.Jira.Markup.LinkType
instance GHC.Classes.Ord Text.Jira.Markup.LinkType
instance GHC.Classes.Eq Text.Jira.Markup.LinkType
instance GHC.Show.Show Text.Jira.Markup.ListStyle
instance GHC.Classes.Ord Text.Jira.Markup.ListStyle
instance GHC.Classes.Eq Text.Jira.Markup.ListStyle
instance GHC.Show.Show Text.Jira.Markup.ColorName
instance GHC.Classes.Ord Text.Jira.Markup.ColorName
instance GHC.Classes.Eq Text.Jira.Markup.ColorName
instance GHC.Show.Show Text.Jira.Markup.URL
instance GHC.Classes.Ord Text.Jira.Markup.URL
instance GHC.Classes.Eq Text.Jira.Markup.URL
instance GHC.Show.Show Text.Jira.Markup.Language
instance GHC.Classes.Ord Text.Jira.Markup.Language
instance GHC.Classes.Eq Text.Jira.Markup.Language
instance GHC.Show.Show Text.Jira.Markup.Parameter
instance GHC.Classes.Ord Text.Jira.Markup.Parameter
instance GHC.Classes.Eq Text.Jira.Markup.Parameter
instance GHC.Show.Show Text.Jira.Markup.Icon
instance GHC.Classes.Ord Text.Jira.Markup.Icon
instance GHC.Classes.Eq Text.Jira.Markup.Icon
instance GHC.Enum.Enum Text.Jira.Markup.Icon
instance GHC.Show.Show Text.Jira.Markup.Inline
instance GHC.Classes.Ord Text.Jira.Markup.Inline
instance GHC.Classes.Eq Text.Jira.Markup.Inline
instance GHC.Show.Show Text.Jira.Markup.Cell
instance GHC.Classes.Ord Text.Jira.Markup.Cell
instance GHC.Classes.Eq Text.Jira.Markup.Cell
instance GHC.Show.Show Text.Jira.Markup.Row
instance GHC.Classes.Ord Text.Jira.Markup.Row
instance GHC.Classes.Eq Text.Jira.Markup.Row
instance GHC.Show.Show Text.Jira.Markup.Block
instance GHC.Classes.Ord Text.Jira.Markup.Block
instance GHC.Classes.Eq Text.Jira.Markup.Block
instance GHC.Show.Show Text.Jira.Markup.Doc
instance GHC.Classes.Ord Text.Jira.Markup.Doc
instance GHC.Classes.Eq Text.Jira.Markup.Doc
-- | Core components of the Jira wiki markup parser.
module Text.Jira.Parser.Core
-- | Jira Parsec parser
type JiraParser = Parsec Text ParserState
-- | Parser state used to keep track of various parameteres.
data ParserState
ParserState :: Bool -> Bool -> Bool -> Bool -> Maybe SourcePos -> Maybe SourcePos -> ParserState
-- | whether the parser is within a link
[stateInLink] :: ParserState -> Bool
-- | whether the parser is within a list
[stateInList] :: ParserState -> Bool
-- | whether the parser is within markup
[stateInMarkup] :: ParserState -> Bool
-- | whether the parser is within a table
[stateInTable] :: ParserState -> Bool
-- | most recent space char position
[stateLastSpcPos] :: ParserState -> Maybe SourcePos
-- | position at which the last string ended
[stateLastStrPos] :: ParserState -> Maybe SourcePos
-- | Default parser state (i.e., start state)
defaultState :: ParserState
-- | Parses a string with the given Jira parser.
parseJira :: JiraParser a -> Text -> Either ParseError a
-- | Set a flag in the parser to True before running a parser,
-- then set the flag's value to False.
withStateFlag :: (Bool -> ParserState -> ParserState) -> JiraParser a -> JiraParser a
-- | Updates the state, marking the current input position as the end of a
-- string.
updateLastStrPos :: JiraParser ()
-- | Updates the state, marking the current input position as the end of a
-- string.
updateLastSpcPos :: JiraParser ()
-- | Returns true when the current parser position is either at the
-- beginning of the document or if the preceding characters did not
-- belong to a string.
notAfterString :: JiraParser Bool
-- | Returns True if the current parser position is
-- directly after a word/string. Returns False if the
-- parser is looking at the first character of the input.
afterString :: JiraParser Bool
-- | Returns True iff the character before the current
-- parser position was a space.
afterSpace :: JiraParser Bool
-- | Succeeds if the parser is looking at the end of a paragraph.
endOfPara :: JiraParser ()
-- | Variant of parsec's notFollowedBy function which properly
-- fails even if the given parser does not consume any input (like
-- eof does).
notFollowedBy' :: Show a => JiraParser a -> JiraParser ()
-- | Like manyTill, but reads at least one item.
many1Till :: Show end => JiraParser a -> JiraParser end -> JiraParser [a]
-- | Parses an empty line, i.e., a line with no chars or whitespace only.
blankline :: JiraParser ()
-- | Skip zero or more space chars.
skipSpaces :: JiraParser ()
blockNames :: [String]
-- | Parses a set of panel parameters
parameters :: JiraParser (Maybe Text, [Parameter])
-- | Parsers whch are shared between multiple modules.
module Text.Jira.Parser.Shared
-- | Parses an icon
icon :: Parsec Text u Icon
-- | Like icon, but doesn't check whether the sequence is followed
-- by a character that would prevent the interpretation as an icon.
icon' :: Parsec Text u Icon
colorName :: Parsec Text u String
-- | Parse Jira wiki inline markup.
module Text.Jira.Parser.Inline
-- | Parses any inline element.
inline :: JiraParser Inline
-- | Parses an anchor into an Anchor element.
anchor :: JiraParser Inline
-- | Parse a plain URL or mail address as AutoLink element.
autolink :: JiraParser Inline
citation :: JiraParser Inline
-- | Text in a different color.
colorInline :: JiraParser Inline
-- | Parses ASCII representation of en-dash or em-dash.
dash :: JiraParser Inline
-- | Parses textual representation of an icon into an Emoji
-- element.
emoji :: JiraParser Inline
-- | Parses an HTML entity into an Entity element.
entity :: JiraParser Inline
-- | Parse image into an Image element.
image :: JiraParser Inline
-- | Parses an in-paragraph newline as a Linebreak element. Both
-- newline characters and double-backslash are recognized as line-breaks.
linebreak :: JiraParser Inline
-- | Parse link into a Link element.
link :: JiraParser Inline
-- | Parses monospaced text into Monospaced.
monospaced :: JiraParser Inline
-- | Parses a special character symbol as a SpecialChar.
specialChar :: JiraParser Inline
-- | Parses a simple, markup-less string into a Str element.
str :: JiraParser Inline
-- | Parses styled text
styled :: JiraParser Inline
-- | Parses whitespace and return a Space element.
whitespace :: JiraParser Inline
-- | Characters which, depending on context, can have a special meaning.
specialChars :: String
-- | Functions for parsing markup-less strings.
module Text.Jira.Parser.PlainText
-- | Parses into an Inline elements which represent plain
-- text. The result consists of any number of Str,
-- SpecialChar, or Space elements.
--
-- This parser can be used to convert un-escaped strings into proper Jira
-- markup elements.
plainText :: Text -> Either ParseError [Inline]
-- | Parse Jira wiki blocks.
module Text.Jira.Parser.Block
-- | Parses any block element.
block :: JiraParser Block
-- | Parses a block quote into a Quote element.
blockQuote :: JiraParser Block
-- | Parses a code block into a Code element.
code :: JiraParser Block
-- | Parses colored text into a Color element.
color :: JiraParser Block
-- | Parses a header line into a Header.
header :: JiraParser Block
-- | Parses four consecutive hyphens as HorizontalRule.
horizontalRule :: JiraParser Block
-- | Parses a list into List.
list :: JiraParser Block
-- | Parses a preformatted text into a NoFormat element.
noformat :: JiraParser Block
-- | Parses a preformatted text into a NoFormat element.
panel :: JiraParser Block
-- | Parses a paragraph into a Para.
para :: JiraParser Block
-- | Parses a table into a Table element.
table :: JiraParser Block
-- | Parse Jira wiki markup.
module Text.Jira.Parser
-- | Parses a document into a Jira AST.
parse :: Text -> Either ParseError Doc
-- | Parses a list of jira blocks into a Doc element.
doc :: JiraParser Doc
-- | Generate Jira wiki markup text from an abstract syntax tree.
module Text.Jira.Printer
-- | Render Jira document as Jira wiki formatted text.
pretty :: Doc -> Text
-- | Render a block as Jira wiki format.
renderBlock :: Block -> JiraPrinter Text
-- | Renders a single inline item as Jira markup.
renderInline :: Inline -> Text
-- | Render a list of Jira blocks as Jira wiki formatted text.
prettyBlocks :: [Block] -> Text
-- | Renders a list of Jira inline markup elements.
prettyInlines :: [Inline] -> Text
type JiraPrinter a = Reader PrinterState a
-- | Internal state used by the printer.
data PrinterState
PrinterState :: Bool -> Text -> PrinterState
[stateInTable] :: PrinterState -> Bool
[stateListLevel] :: PrinterState -> Text
-- | Default start state of the printer.
startState :: PrinterState
-- | Run with default state.
withDefault :: JiraPrinter a -> a