| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- parseTok :: FilePath -> [(Key, RandTok)] -> [Text] -> Text -> Either (ParseErrorBundle Text Void) RandTok
- parseTokM :: [Text] -> Parser (Context RandTok)
- runFile :: [Text] -> FilePath -> IO Text
- parseTree :: FilePath -> [(Key, RandTok)] -> [Text] -> Text -> Either (ParseErrorBundle Text Void) RandTok
- parseFile :: MonadIO m => [Text] -> FilePath -> FilePath -> m (Either (ParseErrorBundle Text Void) RandTok)
- makeTree :: [Text] -> FilePath -> FilePath -> IO (Either (ParseErrorBundle Text Void) RandTok)
- run :: MonadRandom m => RandTok -> m Text
- runText :: MonadRandom m => [Text] -> String -> Text -> m Text
- data RandTok
- type Key = Text
- type Context a = State [(Key, RandTok)] a
- data SemanticError
- cacheFile :: FilePath -> IO Text
- runFileN :: Int -> [Text] -> FilePath -> IO [Text]
- getDir :: FilePath -> FilePath
- displayTree :: RandTok -> String
- madlang :: QuasiQuoter
- madFile :: FilePath -> Q Exp
Parsers for .mad files
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 (ParseErrorBundle Text 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" [] [] fparseTokM :: [Text] -> Parser (Context RandTok) Source #
Parse text as a token + context (aka a reader monad with all the other functions)
Arguments
| :: [Text] | List of variables to substitute into the template |
| -> FilePath | Path to |
| -> IO Text | Result |
Generate randomized text from a file containing a template
parseTree :: FilePath -> [(Key, RandTok)] -> [Text] -> Text -> Either (ParseErrorBundle Text Void) RandTok Source #
Parse text as a token, suitable for printing as a tree..
Arguments
| :: MonadIO m | |
| => [Text] | variables to substitute into the template |
| -> FilePath | folder |
| -> FilePath | filepath within folder |
| -> m (Either (ParseErrorBundle Text Void) RandTok) | parsed |
Parse a template file into the RandTok data type
makeTree :: [Text] -> FilePath -> FilePath -> IO (Either (ParseErrorBundle Text 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.
datatype for a token returning a random string
Instances
| Eq RandTok Source # | |
| Show RandTok Source # | |
| Generic RandTok Source # | |
| Semigroup RandTok Source # | |
| Monoid RandTok Source # | Make (Value "Hello") <> (List [(0.5," you"), (0.5, " me")]) (List [(0.5,"Hello you"), (0.5, "Hello me")]) |
| Lift RandTok Source # | |
| Binary RandTok Source # | |
| Recursive RandTok Source # | |
| Eq a => Eq (Context a) Source # | Compare inside the state monad using only the underlying objects |
| type Rep RandTok Source # | |
Defined in Text.Madlibs.Internal.Types | |
| type Base RandTok Source # | |
Defined in Text.Madlibs.Internal.Types | |
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
data SemanticError Source #
Datatype for a semantic error
Constructors
| NoReturn | |
| CircularFunctionCalls Text Text | |
| InsufficientArgs Int Int | |
| DoubleDefinition Text | |
| NoContext Text | |
| ImportNotFound FilePath |
Instances
| Show SemanticError Source # | display a |
Defined in Text.Madlibs.Cata.SemErr Methods showsPrec :: Int -> SemanticError -> ShowS # show :: SemanticError -> String # showList :: [SemanticError] -> ShowS # | |
| Exception SemanticError Source # | Derived via our show instance; |
Defined in Text.Madlibs.Cata.SemErr Methods toException :: SemanticError -> SomeException # fromException :: SomeException -> Maybe SemanticError # displayException :: SemanticError -> String # | |
Command-line executable
cacheFile :: FilePath -> IO Text Source #
Cache the parsed strucutre (and libraries it depends on) as a binary file `.filename.mbc`, reading instead from it when possible.
displayTree :: RandTok -> String Source #
Draw as a syntax Tree
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.