madlang-3.1.1.7: Randomized templating language DSL

Safe HaskellNone
LanguageHaskell2010

Text.Madlibs

Contents

Description

Madlang Text Generation Library, EDSL, and Interpreted Language

Purpose

Madlang is a text-genrating Domain-Specific Language (DSL). It is similar in purpose to tracery, but it is written in Haskell and therefore offers more flexibility.

Example

In file example.mad: :define gambling 1.0 "heads" 1.0 "tails" :return 1.0 "The result of the coin flip was: " gambling

$ madlang run example.mad
tails

Synopsis

Parsers for .mad files

parseTok Source #

Arguments

:: FilePath

File name to use for parse errors

-> [(Key, RandTok)]

Context, i.e. other random data paired with a key.

-> [Text]

list of variables to substitute into the template

-> Text

Actaul text to parse

-> Either (ParseError Char (ErrorFancy Void)) RandTok

Result

Parse text given a context

import qualified Data.Text.IO as TIO

getParsed = do
    f <- TIO.readFile "template.mad"
    parseTok "filename.mad" [] [] f

parseTokM :: [Text] -> Parser (Context RandTok) Source #

Parse text as a token + context (aka a reader monad with all the other functions)

runFile Source #

Arguments

:: [Text]

List of variables to substitute into the template

-> FilePath

Path to .mad file.

-> IO Text

Result

Generate randomized text from a file containing a template

parseTree :: FilePath -> [(Key, RandTok)] -> [Text] -> Text -> Either (ParseError Char (ErrorFancy Void)) RandTok Source #

Parse text as a token, suitable for printing as a tree..

parseFile Source #

Arguments

:: [Text]

variables to substitute into the template

-> FilePath

folder

-> FilePath

filepath within folder

-> IO (Either (ParseError Char (ErrorFancy Void)) RandTok)

parsed RandTok

Parse a template file into the RandTok data type

makeTree :: [Text] -> FilePath -> FilePath -> IO (Either (ParseError Char (ErrorFancy Void)) RandTok) Source #

Parse a template into a RandTok suitable to be displayed as a tree

Functions and constructs for the RandTok data type

run :: MonadRandom m => RandTok -> m Text Source #

Generate randomized text from a RandTok

getText :: IO T.Text
getText = do
    let exampleTok = List [(1.0,List [(0.5,Value "heads"),(0.5,Value "tails")])]
    run exampleTok

runText :: MonadRandom m => [Text] -> String -> Text -> m Text Source #

Run based on text input, with nothing linked.

data RandTok Source #

datatype for a token returning a random string

Constructors

List [(Prob, RandTok)] 
Value Text 

Instances

Eq RandTok Source # 

Methods

(==) :: RandTok -> RandTok -> Bool #

(/=) :: RandTok -> RandTok -> Bool #

Show RandTok Source # 
Monoid RandTok Source #

Make RandTok a monoid so we can append them together nicely (since they do generate text).

(Value "Hello") <> (List [(0.5," you"), (0.5, " me")])
(List [(0.5,"Hello you"), (0.5, "Hello me")])
Lift RandTok Source # 

Methods

lift :: RandTok -> Q Exp #

Recursive RandTok Source # 

Methods

project :: RandTok -> Base RandTok RandTok #

cata :: (Base RandTok a -> a) -> RandTok -> a #

para :: (Base RandTok (RandTok, a) -> a) -> RandTok -> a #

gpara :: (Corecursive RandTok, Comonad w) => (forall b. Base RandTok (w b) -> w (Base RandTok b)) -> (Base RandTok (EnvT RandTok w a) -> a) -> RandTok -> a #

prepro :: Corecursive RandTok => (forall b. Base RandTok b -> Base RandTok b) -> (Base RandTok a -> a) -> RandTok -> a #

gprepro :: (Corecursive RandTok, Comonad w) => (forall b. Base RandTok (w b) -> w (Base RandTok b)) -> (forall c. Base RandTok c -> Base RandTok c) -> (Base RandTok (w a) -> a) -> RandTok -> a #

Corecursive RandTok Source # 

Methods

embed :: Base RandTok RandTok -> RandTok #

ana :: (a -> Base RandTok a) -> a -> RandTok #

apo :: (a -> Base RandTok (Either RandTok a)) -> a -> RandTok #

postpro :: Recursive RandTok => (forall b. Base RandTok b -> Base RandTok b) -> (a -> Base RandTok a) -> a -> RandTok #

gpostpro :: (Recursive RandTok, Monad m) => (forall b. m (Base RandTok b) -> Base RandTok (m b)) -> (forall c. Base RandTok c -> Base RandTok c) -> (a -> Base RandTok (m a)) -> a -> RandTok #

Eq a => Eq (Context a) Source #

Compare inside the state monad using only the underlying objects

Methods

(==) :: Context a -> Context a -> Bool #

(/=) :: Context a -> Context a -> Bool #

type Base RandTok Source # 

type Key = Text Source #

dataype for a key aka token name

Types associated with the parser

type Context a = State [(Key, RandTok)] a Source #

State monad providing context, i.e. function we've already called before

Command-line executable

runMadlang :: IO () Source #

Main program action

Example Usage:

$ madlang run example.mad
some text generated

Template Haskell EDSL

madlang :: QuasiQuoter Source #

QuasiQuoter for an EDSL, e.g.

demoQQ :: T.Text
demoQQ = run
[madlang|
:define something
    1.0 "hello"
    1.0 "goodbye"
:return
    1.0 something|]

Note that this is in general much faster than running interpreted code, though inclusions do not work in the QuasiQuoter or in spliced expressions.

madFile :: FilePath -> Q Exp Source #

Splice for embedding a '.mad' file, e.g.

demo :: IO T.Text
demo = run
    $(madFile "twitter-bot.mad")

Note that the embedded code cannot have any inclusions.