ogmarkup-2.3: A lightweight markup language for story writers

Copyright(c) Ogma Project, 2016
LicenseMIT
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Text.Ogmarkup.Private.Parser

Description

This module provides several parsers that can be used in order to extract the Ast of an Ogmarkup document.

Please consider that only document should be used outside this module.

Synopsis

Documentation

data ParserState Source #

Keep track of the currently opened formats.

Constructors

ParserState 

Fields

type OgmarkupParser a = StateT ParserState (Parsec Dec a) Source #

An ogmarkup parser processes Char tokens and carries a ParserState.

enterEmph :: Stream a => OgmarkupParser a () Source #

Update the ParserState to guard against nested emphasis.

leaveEmph :: Stream a => OgmarkupParser a () Source #

Update the ParserState to be able to parse input with emphasis again.

enterStrongEmph :: Stream a => OgmarkupParser a () Source #

Update the ParserState to guard against nested strong emphasis.

leaveStrongEmph :: Stream a => OgmarkupParser a () Source #

Update the ParserState to be able to parse input with strong emphasis again.

enterQuote :: Stream a => OgmarkupParser a () Source #

Update the ParserState to guard against nested quoted inputs.

leaveQuote :: Stream a => OgmarkupParser a () Source #

Update the ParserState to be able to parse an input surrounded by quotes again.

initParserState :: ParserState Source #

A initial ParserState instance to be used at the begining of a document parsing.

parse :: (Stream a, Token a ~ Char) => OgmarkupParser a b -> String -> a -> Either (ParseError (Token a) Dec) b Source #

A wrapper around the runParser function of Megaparsec. It uses initParserState as an initial state.

document :: (Stream a, Token a ~ Char, IsString b) => OgmarkupParser a (Document b, a) Source #

Try its best to parse an ogmarkup document. When it encounters an error, it returns an Ast and the remaining input.

See Document.

restOfParagraph :: (Stream a, Token a ~ Char, IsString b) => OgmarkupParser a b Source #

Parse the rest of the current paragraph with no regards for the ogmarkup syntax. This Parser is used when the document is ill-formed, to find a new point of synchronization.

talk Source #

Arguments

:: (Stream a, Token a ~ Char, IsString b) 
=> Char

A character to mark the begining of a reply

-> Char

A character to mark the end of a reply

-> (Reply b -> Maybe b -> Component b)

Either Dialogue or Thought according to the situation

-> OgmarkupParser a (Component b) 

talk c c' constr wraps a reply surrounded by c and c' inside constr (either Dialogue or Thought).

characterName :: (Stream a, Token a ~ Char, IsString b) => OgmarkupParser a b Source #

Parse the name of the character which speaks or thinks. According to the ogmarkup syntax, it is surrounded by parentheses.

reply :: (Stream a, Token a ~ Char, IsString b) => Char -> Char -> OgmarkupParser a (Reply b) Source #

reply parses a Reply.

word :: (Stream a, Token a ~ Char, IsString b) => OgmarkupParser a (Atom b) Source #

See Word. This parser does not consume the following spaces, so the caller needs to take care of it.

longword :: (Stream a, Token a ~ Char, IsString b) => OgmarkupParser a (Atom b) Source #

Wrap a raw string surrounded by ` inside a Word.

>>> parse longword "" "`test *ei*`"
Right (Ast.Word "test *ei*")

Therefore, ` can be used to insert normally reserved symbol inside a generated document.

mark :: (Stream a, Token a ~ Char) => OgmarkupParser a (Atom b) Source #

See Punctuation. Be aware that mark does not parse the quotes because they are processed quote.

openQuote :: (Stream a, Token a ~ Char) => OgmarkupParser a () Source #

See OpenQuote. This parser consumes the following blank (see blank) and skip the result.

closeQuote :: (Stream a, Token a ~ Char) => OgmarkupParser a () Source #

See CloseQuote. This parser consumes the following blank (see blank) and skip the result.

asideSeparator :: (Stream a, Token a ~ Char) => OgmarkupParser a () Source #

An aside section (see Aside) is a particular region surrounded by two lines of underscores (at least three). This parser consumes one such line.

endOfParagraph :: (Stream a, Token a ~ Char) => OgmarkupParser a () Source #

The end of a paragraph is the end of the document or two blank lines or an aside separator, that is a line of underscores.

blank :: (Stream a, Token a ~ Char) => OgmarkupParser a () Source #

This parser consumes all the white spaces until it finds either an aside surrounding marker (see Aside), the end of the document or one blank line. The latter marks the end of the current paragraph.

skip :: Stream a => OgmarkupParser a b -> OgmarkupParser a () Source #

skip p parses p and skips the result.