Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data PNode
- data Token
- transform :: [Token] -> [PNode]
- ast :: [PNode] -> [Token] -> [PNode]
- popNodes :: [PNode] -> (PNode, [PNode], [PNode])
- popNodes_ :: [PNode] -> [PNode] -> (PNode, [PNode], [PNode])
- renderNodes :: [PNode] -> Text
- renderNode :: PNode -> Text
- renderTokens :: [Token] -> Text
- renderToken :: Token -> Text
- parseText :: Text -> Either ParseError [PNode]
- parseEverything :: Parser [Token]
- parseVar :: Parser Token
- parsePreamble :: Parser Token
- parsePreambleStart :: Parser String
- parsePartial :: Parser Token
- parseEscape :: Parser Token
- parseContent :: Parser Token
- parseFor :: Parser Token
- parseIf :: Parser Token
- parseFunction :: String -> (Text -> Token) -> Parser Token
- parseEnd :: Parser Token
- parseFakeVar :: Parser Token
- many1Till :: Stream s m t => ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
- findPreambleText :: [PNode] -> Maybe Text
- isPreamble :: PNode -> Bool
- preambleText :: PNode -> Maybe Text
Documentation
>>>
:set -XOverloadedStrings
>>>
import Data.Either (isLeft)
Pencil's Page
AST.
Pencil's tokens for content.
transform :: [Token] -> [PNode] Source #
Convert Tokens to PNode AST.
>>>
transform [TokText "hello", TokText "world"]
[PText "hello",PText "world"]
>>>
transform [TokIf "title", TokEnd]
[PIf "title" []]
>>>
transform [TokIf "title", TokText "hello", TokText "world", TokEnd]
[PIf "title" [PText "hello",PText "world"]]
${if(title)} ${for(posts)} world ${end} ${end}
>>>
transform [TokIf "title", TokFor "posts", TokText "world", TokEnd, TokEnd]
[PIf "title" [PFor "posts" [PText "world"]]]
begin now ${if(title)} hello world ${if(body)} ${body} ${someothervar} wahh ${end} final thing ${end} the lastline
>>>
transform [TokText "begin", TokText "now", TokIf "title", TokText "hello", TokText "world", TokIf "body", TokVar "body", TokVar "someothervar", TokText "wahh", TokEnd, TokText "final", TokText "thing", TokEnd, TokText "the", TokText "lastline"]
[PText "begin",PText "now",PIf "title" [PText "hello",PText "world",PIf "body" [PVar "body",PVar "someothervar",PText "wahh"],PText "final",PText "thing"],PText "the",PText "lastline"]
<!--PREAMBLE foo: bar do: - re - me --> Hello world ${foo}
>>>
transform [TokPreamble "foo: bar\ndo:\n - re\n -me", TokText "Hello world ", TokVar "foo"]
[PPreamble "foo: bar\ndo:\n - re\n -me",PText "Hello world ",PVar "foo"]
ast :: [PNode] -> [Token] -> [PNode] Source #
Converts Tokens, which is just the raw list of parsed tokens, into PNodes which are the tree-structure expressions (i.e. if/for nesting)
This function works by using a stack to keep track of where we are for nested expressions such as if and for statements. When a token that starts a nesting is found (like a TokIf), a "meta" expression (PMetaIf) is pushed into the stack. When we finally see an end token (TokEnd), we pop all the expressions off the stack until the first meta tag (e.g PMetaIf) is reached. All the expressions popped off are now known to be nested inside that if statement.
popNodes :: [PNode] -> (PNode, [PNode], [PNode]) Source #
Pop nodes until we hit a If/For statement. Return pair (constructor found, nodes popped, remaining stack)
renderNodes :: [PNode] -> Text Source #
Render nodes as string.
renderNode :: PNode -> Text Source #
Render node as string.
renderTokens :: [Token] -> Text Source #
Render tokens.
renderToken :: Token -> Text Source #
Render token.
parseEverything :: Parser [Token] Source #
Parse everything.
>>>
parse parseEverything "" "Hello ${man} and ${woman}."
Right [TokText "Hello ",TokVar "man",TokText " and ",TokVar "woman",TokText "."]
>>>
parse parseEverything "" "Hello ${man} and ${if(woman)} text here ${end}."
Right [TokText "Hello ",TokVar "man",TokText " and ",TokIf "woman",TokText " text here ",TokEnd,TokText "."]
>>>
parse parseEverything "" "Hi ${for(people)} ${name}, ${end} everyone!"
Right [TokText "Hi ",TokFor "people",TokText " ",TokVar "name",TokText ", ",TokEnd,TokText " everyone!"]
>>>
parse parseEverything "" "${realvar} $.get(javascript) $$ $$$ $} $( $45.50 $$escape $${escape2} wonderful life! ${truth}"
Right [TokVar "realvar",TokText " $.get(javascript) $$ $$$ $} $( $45.50 $$escape ",TokText "${",TokText "escape2} wonderful life! ",TokVar "truth"]
>>>
parse parseEverything "" "<!--PREAMBLE \n foo: bar\ndo:\n - re\n -me\n -->waffle house ${lyfe}"
Right [TokPreamble " \n foo: bar\ndo:\n - re\n -me\n ",TokText "waffle house ",TokVar "lyfe"]
>>>
parse parseEverything "" "YO ${foo} <!--PREAMBLE \n ${foo}: bar\ndo:\n - re\n -me\n -->waffle house ${lyfe}"
Right [TokText "YO ",TokVar "foo",TokText " ",TokPreamble " \n ${foo}: bar\ndo:\n - re\n -me\n ",TokText "waffle house ",TokVar "lyfe"]
This is a degenerate case that we will just allow (for now) to go sideways: >>> parse parseEverything "" "bthis ${var never closes/b ${realvar}" Right [TokText "bthis ",TokVar "var never closes/b ${realvar"]
parsePreamble :: Parser Token Source #
Parse preamble.
parsePreambleStart :: Parser String Source #
Parse the start of a PREAMBLE.
parsePartial :: Parser Token Source #
Parse partial commands.
>>>
parse parsePartial "" "${partial(\"my/file/name.html\")}"
Right (TokPartial "my/file/name.html")
parseEscape :: Parser Token Source #
Parse escape sequence "$${"
>>>
parse parseEscape "" "$${example}"
Right (TokText "${")
parseContent :: Parser Token Source #
Parse boring, boring text.
>>>
parse parseContent "" "hello ${ffwe} you!"
Right (TokText "hello ")
>>>
parse parseContent "" "hello $.get() $ $( $$ you!"
Right (TokText "hello $.get() $ $( $$ you!")
Because of our first parser to grab a character that is not a $, we can't grab strings that start with a $, even if it's text. It's a bug, just deal with it for now. >>> isLeft $ parse parseContent "" "$$$ what" True
>>>
isLeft $ parse parseContent "" "${name}!!"
True
parseFor :: Parser Token Source #
Parse for loop declaration.
>>>
parse parseFor "" "${for(posts)}"
Right (TokFor "posts")
>>>
parse parseFor "" "${for(variable name with spaces technically allowed)}"
Right (TokFor "variable name with spaces technically allowed")
>>>
isLeft $ parse parseFor "" "${for()}"
True
>>>
isLeft $ parse parseFor "" "${for foo}"
True
parseFunction :: String -> (Text -> Token) -> Parser Token Source #
General parse template functions.
parseEnd :: Parser Token Source #
Parse end keyword.
>>>
parse parseEnd "" "${end}"
Right TokEnd
>>>
isLeft $ parse parseEnd "" "${enddd}"
True
parseFakeVar :: Parser Token Source #
A hack to capture strings that "almost" are templates. I couldn't figure out another way.
many1Till :: Stream s m t => ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a] Source #
many1Till p end
will parse one or more p
until @end.
From https://hackage.haskell.org/package/pandoc-1.10.0.4/docs/Text-Pandoc-Parsing.html
isPreamble :: PNode -> Bool Source #
Returns True
if the PNode
is a PPreamble
.