[INCLUDE TH/speedbar.blogme]
[SETFAVICON blogme/blogme-icon.png]
[#
(defun c () (interactive) (find-blogme3-sh0-if "blogme3"))
;; http://angg.twu.net/blogme3.html
;; file:///home/edrx/TH/L/blogme3.html
;; (find-fline "~/TH/L/dednat4.html")
;; (find-blogmefile "README")
;; (find-blogmefile "INTERNALS")
;; (find-blogmefile "")
#]
[lua:
-- old stuff:
def [[ QQ 1Q body TT(Q(body)) ]]
def [[ QQQ 1Q body PRE(Q(two_d_trim(body))) ]]
def [[ QQQBOX 1 body
_G["BORDERLESSBOX+"](STYLE("background: #ffda99;"), body) ]]
def [[ QQQ 1Q body QQQBOX(PRE(Q(two_d_trim(body)))) ]]
def [[ INDEXIMG 2 url,alt "
\n" ]]
def [[ ( nop _ "\091" ]]
def [[ ) nop _ "\093" ]]
def [[ FOOTREF 3 label1,label2,text NAME(label1, HREF("#"..label2, text)) ]]
-- 2007apr17, guilherme
def [[ QQQ 1Q body
"
\n"..
"\n"..
Q(two_d_trim(body))..
" \n"..
" |
\n"
]]
def [[ STANDOUT 1 text
"$text"
]]
-- new stuff:
def [[ SPANSTYLE 2 style,body "$body" ]]
def [[ TTSTYLE 2 style,body "$body
" ]]
def [[ PRESTYLE 2 style,body "$body
" ]]
def [[ BORDERLESSTABLE 1 body
"\n" ]]
def [[ PREBOXSTYLE 2 style,body BORDERLESSTABLE(PRESTYLE(style, body)) ]]
-- Forth: #6495ed (find-ecolors "CornflowerBlue")
-- Tcl: #ff6a6a (find-ecolors "IndianRed1")
-- Blogme: #FFda99
-- (find-angg ".emacs" "ee-choosecolor")
-- (find-ecolor-links (ee-choosecolor "#be7326"))
-- (find-ecolor-links "CornFlowerBlue")
-- (find-ecolor-links "#ccddff")
-- (find-ecolors)
thstyle = "background: #fec8cc"
tclstyle = "background: #fec8cc"
luastyle = "background: blue"
--lispstyle = "background: #cffcd2"
lispstyle = "background: #b0fbb5"
htmlstyle = "background: #b0fbb5"
htmlstyle = "background: #d18828"
forthstyle = "background: #c4daf9"
forthostyle = "background: #75affc"
blogmestyle = "background: #ffda99"
prestyle = "; padding: 4px; margin: 0"
def [[ TTTH 1 body TTSTYLE(thstyle , body) ]]
def [[ TTTCL 1 body TTSTYLE(tclstyle , body) ]]
def [[ TTLUA 1 body TTSTYLE(luastyle , body) ]]
def [[ TTLISP 1 body TTSTYLE(lispstyle , body) ]]
def [[ TTHTML 1 body TTSTYLE(htmlstyle , body) ]]
def [[ TTFORTH 1 body TTSTYLE(forthstyle , body) ]]
def [[ TTFORTHO 1 body TTSTYLE(forthostyle, body) ]]
def [[ TTBLOGME 1 body TTSTYLE(blogmestyle, body) ]]
def [[ PREBOXTH 1 body PREBOXSTYLE(thstyle ..prestyle, body) ]]
def [[ PREBOXTCL 1 body PREBOXSTYLE(tclstyle ..prestyle, body) ]]
def [[ PREBOXLUA 1 body PREBOXSTYLE(luastyle ..prestyle, body) ]]
def [[ PREBOXLISP 1 body PREBOXSTYLE(lispstyle ..prestyle, body) ]]
def [[ PREBOXHTML 1 body PREBOXSTYLE(htmlstyle ..prestyle, body) ]]
def [[ PREBOXFORTH 1 body PREBOXSTYLE(forthstyle ..prestyle, body) ]]
def [[ PREBOXBLOGME 1 body PREBOXSTYLE(blogmestyle..prestyle, body) ]]
def [[ TAGGED 3 tag,target,body NAME(tag, HREF("#"..target, body)) ]]
def [[ TOED 3 tag,target,body
NAME(strsub(tag, 2, -2), HREF("#"..strsub(target, 2, -3), body)) ]]
def [[ .SECT 5 n,tag,to1,to2,title TOED(tag, to2, n..". "..title ) ]]
def [[ SECT 5 n,tag,to1,to2,title TOED(tag, to2, H2(n..". "..title)) ]]
def [[ .SUBSECT 5 n,tag,to1,to2,title TOED(tag, to2, n..". "..title ) ]]
def [[ SUBSECT 5 n,tag,to1,to2,title TOED(tag, to2, H3(n..". "..title)) ]]
]
[SETHEADSTYLE
.red { color: red; }
]
[# ------------------------------------------------------------------ #]
[htmlize [J BlogMe3 - an extensible language for generating HTML]
[P ([STANDOUT 2007oct25:] sorry, this is a big mess at the moment -
you came in the middle of a big rewrite. Finishing these docs are my
main priority now, but this will take several days...)]
[# HLIST2 [J Quick index]
]
[#
# «.basic» (to "basic")
# «.parsing-pos-subj» (to "parsing-pos-subj")
# «.evaluation» (to "evaluation")
# «.argument-parsers» (to "argument-parsers")
# «.core-and-angg» (to "core-and-angg")
# «.invoking» (to "invoking")
# «.ancestors» (to "ancestors")
# «.Forth» (to "Forth")
# «.Lisp» (to "Lisp")
# «Tcl» (to ".Tcl")
# «.TH» (to "TH")
# «.source-files» (to "source-files")
# «.brackets.lua» (to "brackets.lua")
# «.definers.lua» (to "definers.lua")
# «.escripts.lua» (to "escripts.lua")
# «.elisp.lua» (to "elisp.lua")
# «.blogme3.lua» (to "blogme3.lua")
# «.introduction» (to "introduction")
# «.language» (to "language")
# «.evaluation» (to "evaluation")
# «.def» (to "def")
# «.internals» (to "internals")
# «.main_tables» (to "main_tables")
# «.tables_for_words» (to "tables_for_words")
# «.parsers» (to "parsers")
# «.files» (to "files")
# «.help-needed» (to "help-needed")
# «.etc» (to "etc")
#]
[WITHINDEX
[RULE -------------------------------------------------------]
[sec «basic» (to ".basic")
H2 [++N]. Basic concepts]
[sec «parsing-pos-subj» (to ".parsing-pos-subj")
H2 [++NN]. Parsing (and pos and subj)]
[P Some of the most fundamental functions in the code of BlogMe are
"parsers". They all try to parse a pattern in the "subject string"
stored in the global variable "subj", starting at the position stored
in the global variable "pos" (the names "subj" and "pos" come from
Icon).]
[BE'
(find-iconbookpage (+ 22 37))
(find-iconbookpage (+ 22 44))
]
[P On success these patterns advance "pos" and return some non-nil
value; on failure they keep "pos" unchanged, and return nil.]
[P Let's fix some terminology. Consider the grammar below; we will
refer to these "patterns" by the names of the "non-terminal symbols",
at the left of the "::=" signs.]
[BE'
spacechar ::= ' ' | '\t' | '\n'
normalchar ::= any char except ' ', '\t', '\n'
wordchar ::= any char except ' ', '\t', '\n', '[', ']'
optspaces ::= spacechar*
spaces ::= spacechar+
wordchars ::= wordchar+
normalchars ::= normalchar+
block ::= '[' (normalchars | block)* ']'
bigword ::= (wordchars | block)+
rest ::= (normalchars | block)*
]
[P All the "*"s and "+"s above are greedy.]
[P Parsers for all these symbols except "bigword" and "rest" can be
implemented using just {lua patterns}; the code is {here}.]
[P As a curiosity, note that "parseblock" could be implemented with
Lua's "balanced pattern" operator, as "[' %b[]]" - but instead of
doing that we use a table that tells for each "[<]" or "[>]" in "subj"
where is the corresponding "[>]" or "[<]". The code is {here} and
{here}.]
[BE'
(find-blogme3file "brackets.lua" "setsubjto =")
(find-blogme3file "brackets.lua" "bracketstructure =")
]
[sec «evaluation» (to ".evaluation")
H2 [++NN]. Evaluation]
[P Parsing, of course, is not enough - what really matters is that
certain "expressions" can be "evaluated". For example, if we evaluate
the following string as a "vblock" ("vblock" stands for the "value of
a block"),]
[BE'
[HREF http://foo/bar/ foo[+ 2 3]bar ploc]
]
[P we get:]
[BE'
foo5bar ploc
]
[P Let's follow in details what is happening here. To evaluate a
block, we first parse its "head word" - HREF, in this case - and then
we parse the "argument list" for that word; how to parse the argument
list depends on the word, as in Lisp and Forth; we will see the
details very soon - and then we call the "blogme code" associated to
HREF, with those arguments; in the case of HREF its blogme code is
stored in a global Lua function with the same name, and so this code
is called as:]
[BE'
HREF("http://foo/bar/", "foo5bar ploc")
]
[P which returns:]
[BE'
foo5bar ploc
]
[P Note that to generate the second argument, "foo5bar ploc", we had
to evaluate the block "[' [+ 2 3]]"; the result was the result of
calling the blogme code for "+" with arguments "2" and "3".]
[sec «argument-parsers» (to ".argument-parsers")
H2 [++NN]. Argument parsers]
[P Just as the blogme code for "HREF" was stored in Lua's table of
globals (_G), the code for the argument parser for "HREF" was stored
in [' _A["HREF"]]. In the case of HREF, the argument parser function
is "readvvrest", whose definition is:]
[BE'
readvvrest = function () return readvword(), readvrest() end
]
[P the "readers" are like the "parsers", but they run "parsespaces()"
before them, and when they "fail" they do not move pos back to before
the spaces, and the return the empty string instead of nil.]
[P Now here are the exact rules for evaluating a block (in pseudocode,
and without any error-checking):]
[BE'
word = getvword()
(_B[word] or _G[word])(_A[word]())
]
[P Note that the table _B is checked before _G - this is to allow us
to have blogme words with the same names as Lua functions, but whose
blogme code is different from the lua function with the same name.]
[P When we evaluate a vword or a vrest we may have to concatenate
several partial results - some from parsing "words" or "normalchars",
some from parsing "blocks" - to form the final result. The convention
(the code is {here}) is that when we only have one partial result
coming from a block, then it is not transformed in any way - this lets
us have blocks that return, say, Lua tables. For example, with the
right (obvious) definitions for "print", "expr:", and "+", this]
[BE'
[print [expr: {2, 3}] [+ 22 33]]
]
[P would print the same output as:]
[BE'
print({2, 3}, 55)
]
[sec «core-and-angg» (to ".core-and-angg")
H2 [++NN]. The core and the angg files]
[sec «invoking» (to ".invoking")
H2 [++NN]. Invoking blogme3.lua]
[P If we are at /tmp, and there's a file /tmp/blogme whose contents are]
[BE'
[lua: print("Hello!")
PP(arg)
]
[htmlize [J Foo Bar]
[P A paragraph]
]
Blah
]
[# (find-es "blogme" "invoking-blogme")
]
[P and we invoke blogme3.lua with arguments "-o foo.html -i
foo.blogme" , we will see something like this,]
[lua:
def [[ /tmp# 1 command COLOR("red", "/tmp#").." "..COLOR("green", command) ]]
]
[PREBOXBLOGME
[/tmp# lua51 ~/blogme3/blogme3.lua -o foo.html -i foo.blogme]
Hello!
{-1="lua51", 0="/home/edrx/blogme3/blogme3.lua",
1="-o", 2="foo.html", 3="-i", 4="foo.blogme"}
[/tmp# cat foo.html]
[Q
Foo Bar
Foo Bar
A paragraph
][/tmp#]
]
[P Let's understand what happened.]
[P The first thing that blogme3.lua does is to extract from [' arg[0]]
the directory where blogme3.lua resides, and add it to the path (the
code is [_ here]; then it loads some files, with]
[BE'
-- (find-blogme3file "blogme3.lua")
require "brackets" -- (find-blogme3 "brackets.lua")
require "definers" -- (find-blogme3 "definers.lua")
require "charset" -- (find-blogme3 "charset.lua")
require "anggdefs" -- (find-blogme3 "anggdefs.lua")
require "elisp" -- (find-blogme3 "elisp.lua")
require "options" -- (find-blogme3 "options.lua")
]
[P then it processes the command-line arguments.]
[P For each recognized command-line argument there is an entry in the
table _O - defined in options.lua - that describes how to process that
option; for example, for "-i" we have this:]
[BE'
-- (find-blogme3 "")
_O["i"] = dooptions_i
dooptions_i = function () ... end
]
[P The loop that processes the options is this simple recursion, in
blogme3.lua:]
[P The argument following "-o" is the name of the output file; as we
shall see (in sec ___), some setup actions can only be performed after
"-o" - for example, all definitions that depend on the base directory
for relative links.]
[P The option "-i" treats the argument following it as the name of an
input file to be evaluated "in the normal way"; the contents of
foo.blogme are evaluated as a "vrest", and the result of this is
discarded (that's why the "Blah" at the end of foo.blogme
disappeared!), but the contents of the global variable _output are
written to the output file, whose name is the global variable _. If
either outfile or the outcontents were empty we would get an error -
but htmlize treated its first argument ("Foo bar") as the title of the
html page ([Q [' "[J Foo bar]" -> "Foo bar"]]), used the "rest" of its
arguments ([' "[P A paragraph]"]) as the body of the html, wrapped
that within html headers, and stored the result in outcontents.]
[P The word "lua:"]
[P (...)]
[RULE -------------------------------------------------------]
[H2 A more precise description]
[P The core of Blogme is made of a parser that recognizes a very
simple language, and an interpreter coupled to the parser; as the
parser goes on processing the input text the interpreter takes the
outputs of the parser and interprets these outputs immediately.]
[P This core engine should the thought as if it had layers. At the
base, a (formal) grammar; then functions that parse and recognize
constructs from that grammar; then functions that take what the parser
reads, assemble that into commands and arguments for those commands,
and execute those commands.]
[P I think that the best way to describe Blogme is to describe these
three layers and the implementation of the top two layers - the
grammar layer doesn't correspond to any code. Looking at the actual
code of the core is very important; the core is not a black box at all
- the variables are made to be read by and changed by user scripts,
and most functions are intended to be replaced by the user eventually,
either by less simplistic versions with more features, or, sometimes,
by functions only thinly connected to the original ones.]
[sec «ancestors» (to ".ancestors")
H2 [++N]. Ancestors]
[# H2 Influences and rationale]
[P I know that it sounds pretentious to say that, but it's true...
Blogme descends from three important "extensible" programming
languages - Forth, Lisp, and Tcl - and from several]
[P The design of Blogme was inspired mainly by - or borrows ideas from
- Forth, Lisp, and Tcl.]
[sec «Forth» (to ".Forth")
H3 [++NN]. Forth]
[P This is a Forth program that prints "[TTFORTHO 3
Hello20]":]
[PREBOXFORTH 1 2 + . ." Hello" 4 5 * .]
[P Forth reads one word at a time and executes it immediately
(sometimes it "compiles" the word instead of running it, but we
can ignore this now). `[TTFORTH .]' is a word that prints the
number at the top of the stack, followed by a space; `[TTFORTH
."]' is a word that prints a string; it's a tricky word because
it [IT interferes on the parsing] to get the string to be
printed. I've always thought that this permission to interfere on
the parsing was one of Forth's most powerful features, and I have
always thought about how to implement something like that - maybe
as an extension - on other languages.]
[P So - the Forth interpreter (actually the "outer interpreter" in
Forth's jargon; the "inner interpreter" is the one that executes
bytecodes) reads the word `[TTFORTH ."]', and then it calls the
associated code to execute it; at that point the pointer to the
input text - let's call it "pos" - is after the space after the
`[TTFORTH ."]', that is, at the `[TTFORTH H]'; the code for
`[TTFORTH ."]' advances pos past the `[TTFORTH Hello"]' and
prints the "[TTFORTHO Hello]", after that the control returns to
the outer interpreter, who happilly goes on to interpret
"[TTFORTH 4 5 * .]", without ever touching the '[TTFORTH
Hello"]'.]
[sec «Lisp» (to ".Lisp")
H3 [++NN]. Lisp]
[P In Lisp all data structures are built from "atoms"
(numbers, strings, symbols) and "conses"; a list like [TTLISP (1 2
3)] is a cons - a pair - holding the "first element of the list",
[TTLISP 1], and the "rest of the list", which is the cons that
represents the list [TTLISP (2 3)]. Trees are also built from
conses and atoms, and programs are trees - there is no distinction
between code and data. The Lisp parser is very simple, and most of
the semantics of Lisp lies in the definition of the "[TTLISP eval]"
function. The main idea that I borrowed from Lisp's "[TTLISP eval]"
is that of having two kinds of evaluation strategies: in]
[PREBOXLISP (* (+ 1 2) (+ 3 4))]
[P the "[TTLISP *]" is a "normal" function, that receives the [IT
results] of [TTLISP (+ 1 2)] and [TTLISP (+ 3 4)] and returns the
result of multiplying those two results; but in]
[PREBOXLISP (if flag (message "yes") (message "no"))]
[P the "[TTLISP if]" is a "special form", that receives its three
arguments unevaluated, then evaluates the first one, "[TTLISP
flag]", to decide if it is going to evaluate the second one or
the third one.]
[sec «.Tcl» (to "Tcl")
H3 [++NN]. Tcl]
[P (3) Tcl. In Tcl the main data structure is the string, and Tcl
doesn't even have the distinction that Lisp has between atoms and
conses - in Tcl numbers, lists, trees and program code are just
strings that can be parsed in certain ways. Tcl has an evaluation
strategy, given by 11 rules, that describes how to "expand", or
"substitute", the parts of the program that are inside [TTTCL ""]s,
[TTTCL [' []]]s, and [TTTCL {}]s (plus rules for "[TTTCL $]"s for
variables, "[TTTCL #]"s for comments, and a few other things). The
[TTTCL ""]-contexts and [TTTCL [' []]]-contexts can nest inside one
another, and what is between [TTTCL {}]s is not expanded, except
for a few backslash sequences. In a sense, what is inside [TTTCL ['
[]]]s is "active code", to be evaluated immediately, while what is
inside [TTTCL {}]s is "passive code", to be evaluated later, if at
all.]
[P Here are some examples of Tcl code:]
[PREBOXTCL ['
set foo 2+3
set bar [expr 2+3]
puts $foo=$bar ;# Prints "2+3=5"
proc square {x} { expr $x*$x }
puts "square 5 = [square 5]" ;# Prints "square 5 = 25"
]]
[sec «TH» (to ".TH")
H3 [++NN]. TH]
[P Blogme descends from a "language" for generating HTML that I
implemented on top of Tcl in 1999; it was called TH. The crucial
feature of Tcl on which TH depended was that [IT in [TTTCL
""]-expansions the whitespace is preserved, but [TTTCL ['
[]]]-blocks are evaluated]. TH scripts could be as simple as
this:]
[PREBOXTCL ['
htmlize {Title of the page} {
[P A paragraph with a [HREF http://foo/bar/ link].]
}
]]
[P but it wasn't hard to construct slightly longer TH scripts in which
a part of the "body of the page" - the second argument to htmlize -
would become, say, an ASCII diagram that would be formatted as a
[TTHTML [Q ...
]] block in the HTML output, keeping all
the whitespace that it had in the script. That would be a bit hard
to do in Lisp; [IT it is only trivial to implement new languages on
top of Lisp when the code for programs in those new languages is
made of atoms and conses]. I wanted something more free-form than
that, and I couldn't do it in Lisp because the Lisp parser can't be
easily changed; also, sometimes, if a portion of the source script
became, say, a cons, I would like to be able to take this cons and
discover from which part of the source script that cons came... in
Blogme this is trivial to do, as [TTBLOGME [' []]]-blocks in the
current Blogme scripts are represented simply by a number - the
position in the script just after the "[TTBLOGME [<]]".]
[sec «source-files» (to ".source-files")
H2 [++N]. The source files]
[sec «brackets.lua» (to ".brackets.lua")
H3 [++NN]. brackets.lua: the parsers (_A and _B)]
[#
#]
[sec «definers.lua» (to ".definers.lua")
H3 [++NN]. definers.lua: def and DEF (_AA)]
[sec «escripts.lua» (to ".escripts.lua")
H3 [++NN]. escripts.lua: htmlizelines (_E)]
[sec «elisp.lua» (to ".elisp.lua")
H3 [++NN]. elisp.lua: makesexphtml (_EHELP, _EBASE, etc)]
[sec «blogme3.lua» (to ".blogme3.lua")
H3 [++NN]. dooptions (_O)]
[RULE -------------------------------------------------------]
[P ([STANDOUT 2007apr18]: Hey! The rest of this page refers to
BlogMe2, that is obsolete... I just finished rewriting it ([Q ->]
[HREF littlelangs.html#blogme3 BlogMe3]), but I haven't had the time
yet to htmlize its docs...)]
[P (2005sep28: I wrote this page in a hurry by htmlizing two of
blogme's documentation files, README and INTERNALS, which are not
very clean...)]
[P See also the [HREF littlelangs.html#blogme [# -> blogme] entry
about BlogMe in my page about little languages].]
[# P [HLIST2 [J Quick index:]
[HREF #introduction Introduction]
[HREF #language How the language works]
[HREF #evaluation How [QQ []]-expressions are evaluated]
[HREF #def Defining new words in Lua with [QQ def]]
[HREF #internals The internals of blogme2.lua]
[HREF #main_tables The main tables used by the program]
[HREF #tables_for_words Blogme words (the tables _W and _A)]
[HREF #parsers The blogme parsers (the table _P)]
[J To be written: [HREF #files files, installing, running the demos,
help needed].]
]]
[# ------------------------------------------------------------------ #]
[sec «introduction» (to ".introduction")
H2 [++N]. Introduction]
[P The "language" that blogme2.lua accepts is extensible and can deal
with input having a lot of explicit mark-up, like this,]
[QQQ
[HLIST2 Items:
[HREF http://foo/bar a link]
[HREF http://another/link]
[IT Italic text]
[BF Boldface]
]
]
[P and conceivably also with input with a lot of [IT implicit] mark-up
and with control structures, like these examples (which haven't been
implemented yet):]
[QQQ
[BLOGME
Tuesday, February 15, 2005
I usually write my notes in plain text files using Emacs; in
these files "["s and "]"s can appear unquoted, urls appear
anywhere without any special markup (like http://angg.twu.net/)
and should be recognized and htmlized to links, some lines are
dates or "anchors" and should be treated in special ways, the
number of blank lines between paragraphs matter, in text
paragraphs maybe _this markup_ should mean bold or italic, and
there may be links to images that should be inlined, etc etc
etc.
]
[IF LOCAL==true
[INCLUDE todo-list.blogme]
]
]
[P BlogMe also support executing blocks of Lua code on-the-fly, like
this:]
[QQQ
[lua:
-- We can put any block of Lua code here
-- as long as its "["s and "]"s are balanced.
]
]
[#
-- The following
def [[ IMAGE 2 url,alt HREF(url, "
"..IMG(url,alt)) ]]
#]
[sec «language» (to ".language")
H2 [++NN]. How the language works]
[P BlogMe's language has only one special syntactical construct, "[QQ
[...]]". There are only have four classes of characters "[(]", "[)]",
whitespace, and "word"; "[QQ [...]]" blocks in the text are treated
specially, and we use Lua's "[QQ %b[]]" regexp-ish construct to skip
over the body of a "[QQ [...]]" quickly, skipping over all balanced
"[QQ []]" pairs inside. The first "word" of such a block (we call it
the "head" of the block) determines how to deal with the "rest" of the
block.]
[P To "evaluate" an expression like]
[QQQ
[HREF http://foo/bar a link]
]
[P we only parse its "head" - "[QQ HREF]" - and then we run the Lua
function called [QQ HREF]. It is up to that function [QQ HREF] to
parse what comes after the head (the "rest"); [QQ HREF] may evaluate
the [QQ []]-expressions in the rest, or use the rest without
evaluations, or even ignore the rest completely. After the execution
of [QQ HREF] the parsing resumes from the point after the associated
"[Q [)]]".]
[sec «evaluation» (to ".evaluation")
H2 [++NN]. How [QQ []]-expressions are evaluated]
[P Actually the evaluation process is a bit more subtle than than. In
the last example, BlogMe doesn't just execute [QQ HREF()]; it uses an
auxiliary table, [QQ _A], and it executes:]
[QQQ HREF(_A["HREF"]())]
[P [QQ _A["HREF"]] returns a function, [QQ vargs2], that uses the rest
to produce arguments for [QQ HREF]. Running [QQ vargs2()] in that
situation returns]
[QQQ "http://foo/bar", "a link"]
[P and [QQ HREF] is called as [QQ HREF("http://foo/bar", "a link")].
So, to define [QQ HREF] as a head all we would need to do ("would"
because it's already defined) is:]
[QQQ
HREF = function (url, text)
return ""..text..""
end
_A["HREF"] = vargs2
]
[sec «def» (to ".def")
H2 [++NN]. Defining new words in Lua with [QQ def]]
[P Defining new heads is so common - and writing out the full Lua code
for a new head, as above, is so boring - that there are several tools
to help us with that. I will explain only one of them, "[QQ def]":]
[QQQ def [[ HREF 2 url,text "$text" ]]]
[P "[QQ def]" is a lua function taking one argument, a string; it
splits that string into its three first "words" (delimited by blanks)
and a "rest"; here is its definition:]
[QQQ
restspecs = {
["1"]=vargs1, ["2"]=vargs2, ["3"]=vargs3, ["4"]=vargs4,
["1L"]=vargs1_a, ["2L"]=vargs2_a, ["3L"]=vargs3_a, ["4L"]=vargs4_a
}
def = function (str)
local _, __, name, restspec, arglist, body =
string.find (str, "^%s*([^%s]+)%s+([^%s]+)%s+([^%s]+)%s(.*)")
_G[name] = lambda(arglist, undollar(body))
_A[name] = restspecs[restspec] or _G[restspec]
or error("Bad restspec: "..name)
end
]
[P The first "word" ("name") is the name of the head that we're
defining; the second "word" ("restspec") determines the _GETARGS
function for that head, and it may be either a special string (one of
the ones registered in the table "restspecs") or the name of a global
function.]
[# ------------------------------------------------------------]
[sec «internals» (to ".internals")
H2 [++N]. The internals of blogme2.lua:]
[sec «main_tables» (to ".main_tables")
H2 [++NN]. The main tables used by the program]
[LIST2
[J [QQ _G]: Lua's [LR
http://www.lua.org/manual/5.0/manual.html#predefined table of globals]]
[J [QQ _W]: blogme words]
[J [QQ _P]: low-level parsers]
[J [QQ _A]: argument-parsing functions for blogme words]
[J [QQ _AA]: abbreviations for argument-parsing functions (see `def')]
[J [QQ _V]: blogme variables (see "$" and `withvars')]
]
[# --------------------]
[sec «tables_for_words» (to ".tables_for_words")
H2 [++NN]. Blogme words (the tables _W and _A)]
[P (Source code: the function `[QQ run_head]', at the end of [AL
blogme/blogme2-inner.lua blogme2-inner.lua].)]
[P Let's examine an example. When blogme processes:]
[QQQ [HREF http://foo bar]]
[P it expands it to:]
[QQQ bar]
[P When the blogme evaluator processes a bracketed expression it first
obtains the first "word" of the brexp (called the "head" of the
brexp), that in this case is "[QQ HREF]"; then it parses and evaluates
the "arguments" of the brexp, and invokes the function associated to
the word "[QQ HREF]" using those arguments. Different words may have
different ways of parsing and evaluating their arguments; this is like
the distinction in Lisp between functions and special forms, and like
the special words like LIT in Forth. Here are the hairy details: if
[QQ HREF] is defined by]
[QQQ
HREF = function (url, str)
return ""..str.."" end
_W["HREF"] = HREF
_A["HREF"] = vargs2
]
[P then the "value" of [QQ [HREF http://foo bar]] will be the same as
the value returned by [QQ HREF("http://foo", "bar")], because]
[QQQ _W["HREF"](_A["HREF"]())]
[P will be the same as:]
[QQQ HREF(vargs2())]
[P when [QQ vargs2] is run the parser is just after the end of the
word "[QQ HREF]" in the brexp, and running [QQ vargs2()] there parses
the rest of the brexp and returns two strings, [QQ "http://foo"] and
[QQ "bar"].]
[P See: (info "(elisp)Function Forms")
[BR] and: (info "(elisp)Special Forms")]
[# --------------------]
[sec «parsers» (to ".parsers")
H2 [++NN]. The blogme parsers (the table _P)]
[P (Corresponding source code: most of [AL blogme/blogme2-inner.lua
blogme2-inner.lua].)]
[P Blogme has a number of low-level parsers, each one identified by a
string (a "blogme pattern"); the (informal) "syntax" of those blogme
patterns was vaguely inspired by Lua5's [HREF
http://www.lua.org/manual/5.0/manual.html#pm syntax for patterns]. In
the table below "BP" stands for "blogme pattern".]
[QQQ
BP Long name/meaning Corresponding Lua pattern
-----+----------------------+--------------------------
"%s" | space char | "[ \t\n]"
"%w" | word char | "[^%[%]]"
"%c" | normal char | "[^ \t\n%[%]]"
"%B" | bracketed expression | "%b[]"
"%W" | bigword | "(%w*%b[]*)*" (but not the empty string!)
]
[P [HLIST2 [J The low-level parsing functions of blogme are of two
kinds (levels):]
[J Functions in the "parse only" level only succeed or fail. When
they succeed they return true and advance the global variable
`pos'; when they fail they return nil and leave pos unchanged
[FOOTREF .partial_failure partial_failure (*)].]
[J Functions in the "parse and process" level are like the
functions in the "parse only" level, but with something extra:
when they succeed they store in the global variable `val' the
"semantic value" of the thing that they parsed. When they fail
they are allowed to garble `val', but they won't change `pos'.]
]]
[P See: (info "(bison)Semantic Values")]
[P These low-level parsing functions are stored in the table `[QQ
_P]', with the index being the "blogme patterns". They use the global
variables `[QQ subj]', `[QQ pos]', `[QQ b]', `[QQ e]', and `[QQ
val]'.]
[P An example: running [QQ _P["%w+"]()] tries to parse a (non-empty)
series of word chars starting at [QQ pos]; running [QQ
_P["%w+:string"]()] does the same, but in case of success the semantic
value is stored into `[QQ val]' as a string -- the comment "[QQ
:string]" in the name of the pattern indicates that this is a "parse
and process" function, and tells something about how the semantic
value is built.]
[P [FOOTREF partial_failure .partial_failure (*)]: Blogme patterns
containing a semicolon (";") violate the convention that says that
patterns that fail do not advance pos. Parsing "A;B" means first
parsing "A", not caring if it succeds or fails, discarding its
semantic value (if any), then parsing "B", and returning the result of
parsing "B". If "A" succeds but "B" fails then "A;B" will fail, but
pos will have been advanced to the end of "A". "A" is usually "%s*".]
[# ------------------------------------------------------------]
[sec «files» (to ".files")
H2 [++NN]. Files]
[P (To do: write this stuff, organize.)]
[P [HLIST2 Files:
[J Its main directory: [A0L blogme/].]
[J Its [AL blogme/README README], and a description of its [AL
blogme/INTERNALS INTERNALS].]
[HLIST2 [J Its source code:]
[AL blogme/blogme2-inner.lua blogme2-inner.lua]
[AL blogme/blogme2-middle.lua blogme2-middle.lua]
[AL blogme/blogme2-outer.lua blogme2-outer.lua]
[AL blogme/blogme2.lua blogme2.lua]
]
[J The [HREF TH/blogme.blogme BlogMe source] for this page.]
[J The [HREF TH/math-b.blogme BlogMe source] for my
[HREF math-b.html math page].]
[J The [HREF speedbar.blogme BlogMe source] for the navigation bar thing.]
]]
[P There is no .tar.gz yet (coming soon!).]
[sec «help-needed» (to ".help-needed")
H2 [++NN]. Help needed]
[P Lua seems to be quite popular in the M$-Windows world, but I
haven't used W$ for anything significative since 1994 and I can't
help with W$-related questions. If you want to try BlogMe on W$ then
please consider writing something about your experience to help the
people coming after you.]
[sec «etc» (to ".etc")
H2 [++NN]. Etc]
[P A [AL .emacs#blogme-mode BlogMe mode for emacs] and [AL
.emacs#favourite-modes a way to switch modes quickly] (with M-m).]
[P [BF A note on usage] (see [AL blogme/blogme2.lua the corresponding
source code]):]
[QQQ blogme2.lua -o foo.html -i foo.blogme]
[P This behaves in a way that is a bit unexpected: what gets written
to foo.html is not the result of "expanding" the contents of
foo.blogme - it's the contents of the variable [QQ blogme_output]. The
function (or "blogme word") [QQ htmlize] sets this variable. Its
source code is [AL blogme/blogme2-outer.lua here].]
[P History: BlogMe is the result of many years playing with little
languages; see [HREF [-> littlelangs] this page]. BlogMe borrowed many
ideas from Forth, Tcl and Lisp.]
[P [HREF [-> contact] How to get in touch with the author.]]
[RULE -------------------------------------------------------]
[# #]
[PREBOXBLOGME [lua: return ls2html("blogme3/") ]]
[RULE -------------------------------------------------------]
[P A test (2007apr26):]
[lua: loada2html()
code_c_d_local ("localc", "locald/")
code_c_d_remote("remotec", "http://foo.bar/remoted/")
def [[ HTMLIZELINES 1 body htmlizelines(body) ]]
-- (find-blogme3file "elisp.lua")
]
[PREBOXBLOGME [HTMLIZELINES [Q ['
#
# (find-localcfile "foo/")
# (find-localcfile "foo/" "ignored")
# (find-localc "foo/" "should be ignored?")
# (find-localc "foo/bar" "becomes a tag")
# (find-localcw3m "foo/bar.html#tag" "ignored")
# (find-remotecfile "foo/")
# (find-remotecfile "foo/" "ignored")
# (find-remotec "foo/" "should be ignored?")
# (find-remotec "foo/bar" "becomes a tag")
# (find-remotecw3m "foo/bar.html#tag" "ignored")
]]]]
[P]
[RULE -------------------------------------------------------]
]
]
[#
# Local Variables:
# coding: raw-text-unix
# modes: (fundamental-mode blogme-mode)
# End:
#]