ogmarkup-5.0: A lightweight markup language for story writers

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

Text.Ogmarkup.Private.Generator

Contents

Description

The generation of the output from an Ast is carried out by the Generator Monad.

Synopsis

The Generator Monad

newtype Generator c a x Source #

The Generator Monad is eventually used to generate an output from a given 'Ast.Document. Internally, it keeps track of the previous processed Atom in order to deal with atom separation.

Constructors

Generator 

Fields

Instances

Monad (Generator c a) Source # 

Methods

(>>=) :: Generator c a a -> (a -> Generator c a b) -> Generator c a b #

(>>) :: Generator c a a -> Generator c a b -> Generator c a b #

return :: a -> Generator c a a #

fail :: String -> Generator c a a #

Functor (Generator c a) Source # 

Methods

fmap :: (a -> b) -> Generator c a a -> Generator c a b #

(<$) :: a -> Generator c a b -> Generator c a a #

Applicative (Generator c a) Source # 

Methods

pure :: a -> Generator c a a #

(<*>) :: Generator c a (a -> b) -> Generator c a a -> Generator c a b #

liftA2 :: (a -> b -> c) -> Generator c a a -> Generator c a b -> Generator c a c #

(*>) :: Generator c a a -> Generator c a b -> Generator c a b #

(<*) :: Generator c a a -> Generator c a b -> Generator c a a #

MonadState (a, Maybe (Atom a)) (Generator c a) Source # 

Methods

get :: Generator c a (a, Maybe (Atom a)) #

put :: (a, Maybe (Atom a)) -> Generator c a () #

state :: ((a, Maybe (Atom a)) -> (a, (a, Maybe (Atom a)))) -> Generator c a a #

runGenerator Source #

Arguments

:: Monoid a 
=> Generator c a x

The Generator to run

-> a

The output

Run a Generator monad and get the generated output. The output type has to implement the class Monoid because the Generator monad uses the mempty constant as the initial state of the output and then uses mappend to expand the result as it processes the generation.

Low-level Generators

apply Source #

Arguments

:: Monoid a 
=> Template a

The Template to apply

-> Generator c a x

The Generator to run

-> Generator c a () 

Apply a template to the result of a given Generator before appending it to the previously generated output.

reset :: Generator c a () Source #

Forget about the past and consider the next Atom as the first to be processed.

raw Source #

Arguments

:: Monoid a 
=> a

A sub-output to append

-> Generator c a () 

Append a new sub-output to the generated output.

AST Processing Generators

atom :: forall c a. (Monoid a, GenConf c a) => Atom a -> Generator c a () Source #

Process an Atom and deal with the space to use to separate it from the paramter of the previous call (that is the last processed Atom).

maybeAtom :: (Monoid a, GenConf c a) => Maybe (Atom a) -> Generator c a () Source #

Call atom if the parameter is not Nothing. Otherwise, do nothing.

atoms :: (Monoid a, GenConf c a) => [Atom a] -> Generator c a () Source #

Process a sequence of Atom.

format :: forall c a. (Monoid a, GenConf c a) => Format a -> Generator c a () Source #

Process a Format.

formats :: (Monoid a, GenConf c a) => [Format a] -> Generator c a () Source #

Process a sequence of Format.

reply :: forall c a. (Monoid a, GenConf c a) => Maybe (Atom a) -> Maybe (Atom a) -> Reply a -> Generator c a () Source #

Process a Reply.

component Source #

Arguments

:: (Monoid a, GenConf c a) 
=> Bool

Was the last component a piece of dialog?

-> Bool

Will the next component be a piece of dialog?

-> Component a

The current component to process

-> Generator c a () 

Process a Component.

paragraph :: forall c a. (Monoid a, GenConf c a) => Paragraph a -> Generator c a () Source #

Process a Paragraph and deal with sequence of Reply.

paragraphs :: (Monoid a, GenConf c a) => [Paragraph a] -> Generator c a () Source #

Process a sequence of Paragraph.

section :: forall c a. (Monoid a, GenConf c a) => Section a -> Generator c a () Source #

Process a Section.

sections :: (Monoid a, GenConf c a) => [Section a] -> Generator c a () Source #

Process a sequence of Section.

document :: forall c a. (Monoid a, GenConf c a) => Document a -> Generator c a () Source #

Process a Document, that is a complete Ogmarkup document.