Просмотр исходного кода

Merge pull request #79 from kaos/zotonic

Support for dynamically extending the template language at template compile time
Evan Miller 12 лет назад
Родитель
Сommit
d20b53f048

+ 1 - 0
.gitignore

@@ -3,3 +3,4 @@ ebin
 erl_crash.dump
 examples/rendered_output
 src/erlydtl_parser.erl
+*~

+ 1 - 1
Emakefile

@@ -1 +1 @@
-{"tests/src/*", [debug_info, {outdir, "ebintest"}]}.
+{"tests/src/*", [debug_info, {outdir, "ebintest"}, {i, "include"}]}.

+ 3 - 2
Makefile

@@ -1,14 +1,15 @@
 ERL=erl
+ERLC=erlc
 REBAR=./rebar
 
-
 all: compile
 
-compile: 
+compile:
 	@$(REBAR) compile
 
 compile_test:
 	-mkdir -p ebintest
+	$(ERLC) -o tests/src -I include/erlydtl_preparser.hrl tests/src/erlydtl_extension_testparser.yrl
 	$(ERL) -make
 
 test: compile compile_test

+ 8 - 0
include/erlydtl_ext.hrl

@@ -0,0 +1,8 @@
+
+-record(scanner_state,
+	{
+	  template=[],
+	  scanned=[],
+	  pos={1,1},
+	  state=in_text
+	}).

+ 216 - 0
include/erlydtl_preparser.hrl

@@ -0,0 +1,216 @@
+%% -*- mode: erlang -*-
+%% vim: syntax=erlang
+
+%% This file is based on the yeccpre.hrl file found here:
+%% -file("/usr/lib/erlang/lib/parsetools-2.0.6/include/yeccpre.hrl", 0).
+%%
+%% The applied modifiactions are to enable the caller to recover
+%% after a parse error, and then resume normal parsing.
+
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
+%%
+%% The contents of this file are subject to the Erlang Public License,
+%% Version 1.1, (the "License"); you may not use this file except in
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+% The parser generator will insert appropriate declarations before this line.%
+
+-export([parse/1, parse_and_scan/1, format_error/1, resume/1]).
+
+-type yecc_ret() :: {'error', _} | {'ok', _}.
+
+-spec parse(Tokens :: list()) -> yecc_ret().
+parse(Tokens) ->
+    yeccpars0(Tokens, {no_func, no_line}, 0, [], []).
+
+-spec parse_and_scan({function() | {atom(), atom()}, [_]}
+                     | {atom(), atom(), [_]}) -> yecc_ret().
+parse_and_scan({F, A}) -> % Fun or {M, F}
+    yeccpars0([], {{F, A}, no_line}, 0, [], []);
+parse_and_scan({M, F, A}) ->
+    yeccpars0([], {{{M, F}, A}, no_line}, 0, [], []).
+
+resume([Tokens, Tzr, State, States, Vstack]) ->
+    yeccpars0(Tokens, Tzr, State, States, Vstack).
+
+-spec format_error(any()) -> [char() | list()].
+format_error(Message) ->
+    case io_lib:deep_char_list(Message) of
+        true ->
+            Message;
+        _ ->
+            io_lib:write(Message)
+    end.
+
+%% To be used in grammar files to throw an error message to the parser
+%% toplevel. Doesn't have to be exported!
+-compile({nowarn_unused_function, return_error/2}).
+-spec return_error(integer(), any()) -> no_return().
+return_error(Line, Message) ->
+    throw({error, {Line, ?MODULE, Message}}).
+
+-compile({nowarn_unused_function, return_state/0}).
+return_state() ->
+    throw(return_state).
+
+-define(CODE_VERSION, "1.4").
+
+yeccpars0(Tokens, Tzr, State, States, Vstack) ->
+    try yeccpars1(Tokens, Tzr, State, States, Vstack)
+    catch 
+        error: Error ->
+            Stacktrace = erlang:get_stacktrace(),
+            try yecc_error_type(Error, Stacktrace) of
+                Desc ->
+                    erlang:raise(error, {yecc_bug, ?CODE_VERSION, Desc},
+                                 Stacktrace)
+            catch _:_ -> erlang:raise(error, Error, Stacktrace)
+            end;
+        %% Probably thrown from return_error/2:
+        throw: {error, {_Line, ?MODULE, _M}} = Error ->
+            Error
+    end.
+
+yecc_error_type(function_clause, [{?MODULE,F,ArityOrArgs} | _]) ->
+    case atom_to_list(F) of
+        "yeccgoto_" ++ SymbolL ->
+            {ok,[{atom,_,Symbol}],_} = erl_scan:string(SymbolL),
+            State = case ArityOrArgs of
+                        [S,_,_,_,_,_,_] -> S;
+                        _ -> state_is_unknown
+                    end,
+            {Symbol, State, missing_in_goto_table}
+    end.
+
+-define(checkparse(CALL, STATE),
+	try case CALL of
+		{error, Error} ->
+		    {error, Error, STATE};
+		Else ->
+		    Else
+	    end
+	catch 
+	    throw: return_state ->
+		{ok, STATE}
+	end).
+    
+yeccpars1([Token | Tokens], Tzr, State, States, Vstack) ->
+    ?checkparse(
+       yeccpars2(State, element(1, Token), States, Vstack, Token, Tokens, Tzr),
+       [[Token|Tokens], Tzr, State, States, Vstack]
+      );
+yeccpars1([], {{F, A},_Line}, State, States, Vstack) ->
+    case apply(F, A) of
+        {ok, Tokens, Endline} ->
+            yeccpars1(Tokens, {{F, A}, Endline}, State, States, Vstack);
+        {eof, Endline} ->
+            yeccpars1([], {no_func, Endline}, State, States, Vstack);
+        {error, Descriptor, _Endline} ->
+            {error, Descriptor}
+    end;
+yeccpars1([], {no_func, no_line}, State, States, Vstack) ->
+    Line = 999999,
+    yeccpars2(State, '$end', States, Vstack, yecc_end(Line), [],
+              {no_func, Line});
+yeccpars1([], {no_func, Endline}, State, States, Vstack) ->
+    yeccpars2(State, '$end', States, Vstack, yecc_end(Endline), [],
+              {no_func, Endline}).
+
+%% yeccpars1/7 is called from generated code.
+%%
+%% When using the {includefile, Includefile} option, make sure that
+%% yeccpars1/7 can be found by parsing the file without following
+%% include directives. yecc will otherwise assume that an old
+%% yeccpre.hrl is included (one which defines yeccpars1/5).
+yeccpars1(State1, State, States, Vstack, Token0, [Token | Tokens], Tzr) ->
+    ?checkparse(
+       yeccpars2(State, element(1, Token), [State1 | States],
+		 [Token0 | Vstack], Token, Tokens, Tzr),
+       [[Token0, Token | Tokens], Tzr, State1, States, Vstack]
+      );
+yeccpars1(State1, State, States, Vstack, Token0, [], {{_F,_A}, _Line}=Tzr) ->
+    yeccpars1([], Tzr, State, [State1 | States], [Token0 | Vstack]);
+yeccpars1(State1, State, States, Vstack, Token0, [], {no_func, no_line}) ->
+    Line = yecctoken_end_location(Token0),
+    yeccpars2(State, '$end', [State1 | States], [Token0 | Vstack],
+              yecc_end(Line), [], {no_func, Line});
+yeccpars1(State1, State, States, Vstack, Token0, [], {no_func, Line}) ->
+    yeccpars2(State, '$end', [State1 | States], [Token0 | Vstack],
+              yecc_end(Line), [], {no_func, Line}).
+
+%% For internal use only.
+yecc_end({Line,_Column}) ->
+    {'$end', Line};
+yecc_end(Line) ->
+    {'$end', Line}.
+
+yecctoken_end_location(Token) ->
+    try
+        {text, Str} = erl_scan:token_info(Token, text),
+        {line, Line} = erl_scan:token_info(Token, line),
+        Parts = re:split(Str, "\n"),
+        Dline = length(Parts) - 1,
+        Yline = Line + Dline,
+        case erl_scan:token_info(Token, column) of
+            {column, Column} ->
+                Col = byte_size(lists:last(Parts)),
+                {Yline, Col + if Dline =:= 0 -> Column; true -> 1 end};
+            undefined ->
+                Yline
+        end
+    catch _:_ ->
+        yecctoken_location(Token)
+    end.
+
+-compile({nowarn_unused_function, yeccerror/1}).
+yeccerror(Token) ->
+    Text = yecctoken_to_string(Token),
+    Location = yecctoken_location(Token),
+    {error, {Location, ?MODULE, ["syntax error before: ", Text]}}.
+
+-compile({nowarn_unused_function, yecctoken_to_string/1}).
+yecctoken_to_string(Token) ->
+    case catch erl_scan:token_info(Token, text) of
+        {text, Txt} -> Txt;
+        _ -> yecctoken2string(Token)
+    end.
+
+yecctoken_location(Token) ->
+    case catch erl_scan:token_info(Token, location) of
+        {location, Loc} -> Loc;
+        _ -> element(2, Token)
+    end.
+
+-compile({nowarn_unused_function, yecctoken2string/1}).
+yecctoken2string({atom, _, A}) -> io_lib:write(A);
+yecctoken2string({integer,_,N}) -> io_lib:write(N);
+yecctoken2string({float,_,F}) -> io_lib:write(F);
+yecctoken2string({char,_,C}) -> io_lib:write_char(C);
+yecctoken2string({var,_,V}) -> io_lib:format("~s", [V]);
+yecctoken2string({string,_,S}) -> io_lib:write_unicode_string(S);
+yecctoken2string({reserved_symbol, _, A}) -> io_lib:write(A);
+yecctoken2string({_Cat, _, Val}) -> io_lib:format("~p",[Val]);
+yecctoken2string({dot, _}) -> "'.'";
+yecctoken2string({'$end', _}) ->
+    [];
+yecctoken2string({Other, _}) when is_atom(Other) ->
+    io_lib:write(Other);
+yecctoken2string(Other) ->
+    io_lib:write(Other).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+

+ 1 - 0
rebar.config

@@ -1 +1,2 @@
 {erl_opts, [debug_info]}.
+{yrl_opts, [{includefile, "include/erlydtl_preparser.hrl"}]}.

+ 692 - 602
src/erlydtl_compiler.erl

@@ -2,6 +2,7 @@
 %%% File:      erlydtl_compiler.erl
 %%% @author    Roberto Saccon <rsaccon@gmail.com> [http://rsaccon.com]
 %%% @author    Evan Miller <emmiller@gmail.com>
+%%% @author    Andreas Stenius <kaos@astekk.se>
 %%% @copyright 2008 Roberto Saccon, Evan Miller
 %%% @doc  
 %%% ErlyDTL template compiler
@@ -34,45 +35,51 @@
 -module(erlydtl_compiler).
 -author('rsaccon@gmail.com').
 -author('emmiller@gmail.com').
+-author('Andreas Stenius <kaos@astekk.se>').
 
 %% --------------------------------------------------------------------
 %% Definitions
 %% --------------------------------------------------------------------
 -export([compile/2, compile/3, compile_dir/2, compile_dir/3, parse/1]).
 
+%% exported for use by extension modules
+-export([merge_info/2, value_ast/5]).
+
 -record(dtl_context, {
-    local_scopes = [], 
-    block_dict = dict:new(), 
-    blocktrans_fun = none,
-    blocktrans_locales = [],
-    auto_escape = off, 
-    doc_root = "", 
-    parse_trail = [],
-    vars = [],
-    filter_modules = [],
-    custom_tags_dir = [],
-    custom_tags_modules = [],
-    reader = {file, read_file},
-    module = [],
-    compiler_options = [verbose, report_errors],
-    binary_strings = true,
-    force_recompile = false,
-    locale = none,
-    verbose = false,
-    is_compiling_dir = false}).
+	  local_scopes = [], 
+	  block_dict = dict:new(), 
+	  blocktrans_fun = none,
+	  blocktrans_locales = [],
+	  auto_escape = off, 
+	  doc_root = "", 
+	  parse_trail = [],
+	  vars = [],
+	  filter_modules = [],
+	  custom_tags_dir = [],
+	  custom_tags_modules = [],
+	  reader = {file, read_file},
+	  module = [],
+	  compiler_options = [verbose, report_errors],
+	  binary_strings = true,
+	  force_recompile = false,
+	  locale = none,
+	  verbose = false,
+	  is_compiling_dir = false,
+	  extension_module = undefined
+	 }).
 
 -record(ast_info, {
-    dependencies = [],
-    translatable_strings = [],
-    translated_blocks= [],
-    custom_tags = [],
-    var_names = [],
-    pre_render_asts = []}).
-    
+	  dependencies = [],
+	  translatable_strings = [],
+	  translated_blocks= [],
+	  custom_tags = [],
+	  var_names = [],
+	  pre_render_asts = []}).
+
 -record(treewalker, {
-    counter = 0,
-    safe = false
-}).    
+	  counter = 0,
+	  safe = false
+	 }).    
 
 compile(Binary, Module) when is_binary(Binary) ->
     compile(Binary, Module, []);
@@ -83,10 +90,10 @@ compile(File, Module) ->
 compile(Binary, Module, Options) when is_binary(Binary) ->
     File = "",
     CheckSum = "",
-    case parse(Binary) of
+    Context = init_dtl_context(File, Module, Options),
+    case parse(Binary, Context) of
         {ok, DjangoParseTree} ->
-            case compile_to_binary(File, DjangoParseTree, 
-                    init_dtl_context(File, Module, Options), CheckSum) of
+            case compile_to_binary(File, DjangoParseTree, Context, CheckSum) of
                 {ok, Module1, _, _} ->
                     {ok, Module1};
                 Err ->
@@ -95,7 +102,7 @@ compile(Binary, Module, Options) when is_binary(Binary) ->
         Err ->
             Err
     end;
-    
+
 compile(File, Module, Options) ->  
     Context = init_dtl_context(File, Module, Options),
     case parse(File, Context) of  
@@ -111,7 +118,7 @@ compile(File, Module, Options) ->
         Err ->
             Err
     end.
-    
+
 
 compile_dir(Dir, Module) ->
     compile_dir(Dir, Module, []).
@@ -122,25 +129,25 @@ compile_dir(Dir, Module, Options) ->
     %% files ending in "~").
     Files = filelib:fold_files(Dir, ".+[^~]$", true, fun(F1,Acc1) -> [F1 | Acc1] end, []),
     {ParserResults, ParserErrors} = lists:foldl(fun
-            (File, {ResultAcc, ErrorAcc}) ->
-                case filename:basename(File) of
-                    "."++_ ->
-                        {ResultAcc, ErrorAcc};
-                    _ ->
-                        FilePath = filename:absname(File),
-                        case filelib:is_dir(FilePath) of
-                            true ->
-                                {ResultAcc, ErrorAcc};
-                            false ->
-                                case parse(FilePath, Context) of
-                                    ok -> {ResultAcc, ErrorAcc};
-                                    {ok, DjangoParseTree, CheckSum} -> 
-                                        {[{File, DjangoParseTree, CheckSum}|ResultAcc], ErrorAcc};
-                                    Err -> {ResultAcc, [Err|ErrorAcc]}
-                                end
-                        end
-                end
-        end, {[], []}, Files),
+						    (File, {ResultAcc, ErrorAcc}) ->
+						       case filename:basename(File) of
+							   "."++_ ->
+							       {ResultAcc, ErrorAcc};
+							   _ ->
+							       FilePath = filename:absname(File),
+							       case filelib:is_dir(FilePath) of
+								   true ->
+								       {ResultAcc, ErrorAcc};
+								   false ->
+								       case parse(FilePath, Context) of
+									   ok -> {ResultAcc, ErrorAcc};
+									   {ok, DjangoParseTree, CheckSum} -> 
+									       {[{File, DjangoParseTree, CheckSum}|ResultAcc], ErrorAcc};
+									   Err -> {ResultAcc, [Err|ErrorAcc]}
+								       end
+							       end
+						       end
+					       end, {[], []}, Files),
     case ParserErrors of
         [] ->
             case compile_multiple_to_binary(Dir, ParserResults, Context) of
@@ -167,37 +174,37 @@ write_binary(Module1, Bin, Options, Warnings) ->
             BeamFile = filename:join([OutDir, atom_to_list(Module1) ++ ".beam"]),
 
             print(Verbose, "Template module: ~w -> ~s~s\n",
-                [Module1, BeamFile,
-                    case Warnings of
-                        [] -> "";
-                        _  -> io_lib:format("\n  Warnings: ~p", [Warnings])
-                    end]),
+		  [Module1, BeamFile,
+		   case Warnings of
+		       [] -> "";
+		       _  -> io_lib:format("\n  Warnings: ~p", [Warnings])
+		   end]),
 
             case file:write_file(BeamFile, Bin) of
                 ok ->
                     ok;
                 {error, Reason} ->
                     {error, lists:flatten(
-                        io_lib:format("Beam generation of '~s' failed: ~p",
-                            [BeamFile, file:format_error(Reason)]))}
+			      io_lib:format("Beam generation of '~s' failed: ~p",
+					    [BeamFile, file:format_error(Reason)]))}
             end
     end.
 
 compile_multiple_to_binary(Dir, ParserResults, Context) ->
     MatchAst = options_match_ast(), 
     {Functions, {AstInfo, _}} = lists:mapfoldl(fun({File, DjangoParseTree, CheckSum}, {AstInfo, TreeWalker}) ->
-                FilePath = full_path(File, Context#dtl_context.doc_root),
-                {{BodyAst, BodyInfo}, TreeWalker1} = with_dependency({FilePath, CheckSum}, body_ast(DjangoParseTree, Context, TreeWalker)),
-                FunctionName = filename:rootname(filename:basename(File)),
-                Function1 = erl_syntax:function(erl_syntax:atom(FunctionName),
-                    [erl_syntax:clause([erl_syntax:variable("_Variables")], none,
-                            [erl_syntax:application(none, erl_syntax:atom(FunctionName), 
-                                    [erl_syntax:variable("_Variables"), erl_syntax:list([])])])]),
-                Function2 = erl_syntax:function(erl_syntax:atom(FunctionName), 
-                    [erl_syntax:clause([erl_syntax:variable("_Variables"), erl_syntax:variable("RenderOptions")], none,
-                            MatchAst ++ [BodyAst])]),
-                {{FunctionName, Function1, Function2}, {merge_info(AstInfo, BodyInfo), TreeWalker1}}
-        end, {#ast_info{}, #treewalker{}}, ParserResults),
+						       FilePath = full_path(File, Context#dtl_context.doc_root),
+						       {{BodyAst, BodyInfo}, TreeWalker1} = with_dependency({FilePath, CheckSum}, body_ast(DjangoParseTree, Context, TreeWalker)),
+						       FunctionName = filename:rootname(filename:basename(File)),
+						       Function1 = erl_syntax:function(erl_syntax:atom(FunctionName),
+										       [erl_syntax:clause([erl_syntax:variable("_Variables")], none,
+													  [erl_syntax:application(none, erl_syntax:atom(FunctionName), 
+																  [erl_syntax:variable("_Variables"), erl_syntax:list([])])])]),
+						       Function2 = erl_syntax:function(erl_syntax:atom(FunctionName), 
+										       [erl_syntax:clause([erl_syntax:variable("_Variables"), erl_syntax:variable("RenderOptions")], none,
+													  MatchAst ++ [BodyAst])]),
+						       {{FunctionName, Function1, Function2}, {merge_info(AstInfo, BodyInfo), TreeWalker1}}
+					       end, {#ast_info{}, #treewalker{}}, ParserResults),
     Forms = custom_forms(Dir, Context#dtl_context.module, Functions, AstInfo),
     compile_forms_and_reload(Dir, Forms, Context#dtl_context.compiler_options).
 
@@ -207,7 +214,7 @@ compile_to_binary(File, DjangoParseTree, Context, CheckSum) ->
             try custom_tags_ast(BodyInfo#ast_info.custom_tags, Context, BodyTreeWalker) of
                 {{CustomTagsAst, CustomTagsInfo}, _} ->
                     Forms = forms(File, Context#dtl_context.module, {BodyAst, BodyInfo}, 
-                        {CustomTagsAst, CustomTagsInfo}, Context#dtl_context.binary_strings, CheckSum), 
+				  {CustomTagsAst, CustomTagsInfo}, Context#dtl_context.binary_strings, CheckSum), 
                     compile_forms_and_reload(File, Forms, Context#dtl_context.compiler_options)
             catch 
                 throw:Error -> Error
@@ -217,6 +224,12 @@ compile_to_binary(File, DjangoParseTree, Context, CheckSum) ->
     end.
 
 compile_forms_and_reload(File, Forms, CompilerOptions) ->
+    case proplists:get_value(debug_compiler, CompilerOptions) of
+	true ->
+	    io:format("Template ~p compiled with options: ~p~n", [File, CompilerOptions]),
+	    [io:format("~s~n", [erl_pp:form(Form)]) || Form <- Forms];
+	_ -> nop
+    end,
     case compile:forms(Forms, CompilerOptions) of
         {ok, Module1, Bin} -> 
             load_code(Module1, Bin, []);
@@ -227,7 +240,7 @@ compile_forms_and_reload(File, Forms, CompilerOptions) ->
         OtherError ->
             OtherError
     end.
-                
+
 load_code(Module, Bin, Warnings) ->
     code:purge(Module),
     case code:load_binary(Module, atom_to_list(Module) ++ ".erl", Bin) of
@@ -238,22 +251,24 @@ load_code(Module, Bin, Warnings) ->
 init_context(IsCompilingDir, ParseTrail, DefDir, Module, Options) ->
     Ctx = #dtl_context{},
     #dtl_context{
-        parse_trail = ParseTrail,
-        module = Module,
-        doc_root = proplists:get_value(doc_root, Options, DefDir),
-        filter_modules = proplists:get_value(custom_filters_modules, Options, Ctx#dtl_context.filter_modules) ++ [erlydtl_filters],
-        custom_tags_dir = proplists:get_value(custom_tags_dir, Options, filename:join([erlydtl_deps:get_base_dir(), "priv", "custom_tags"])),
-        custom_tags_modules = proplists:get_value(custom_tags_modules, Options, Ctx#dtl_context.custom_tags_modules),
-        blocktrans_fun = proplists:get_value(blocktrans_fun, Options, Ctx#dtl_context.blocktrans_fun),
-        blocktrans_locales = proplists:get_value(blocktrans_locales, Options, Ctx#dtl_context.blocktrans_locales),
-        vars = proplists:get_value(vars, Options, Ctx#dtl_context.vars), 
-        reader = proplists:get_value(reader, Options, Ctx#dtl_context.reader),
-        compiler_options = proplists:get_value(compiler_options, Options, Ctx#dtl_context.compiler_options),
-        binary_strings = proplists:get_value(binary_strings, Options, Ctx#dtl_context.binary_strings),
-        force_recompile = proplists:get_value(force_recompile, Options, Ctx#dtl_context.force_recompile),
-        locale = proplists:get_value(locale, Options, Ctx#dtl_context.locale),
-        verbose = proplists:get_value(verbose, Options, Ctx#dtl_context.verbose),
-        is_compiling_dir = IsCompilingDir}.
+		  parse_trail = ParseTrail,
+		  module = Module,
+		  doc_root = proplists:get_value(doc_root, Options, DefDir),
+		  filter_modules = proplists:get_value(custom_filters_modules, Options, Ctx#dtl_context.filter_modules) ++ [erlydtl_filters],
+		  custom_tags_dir = proplists:get_value(custom_tags_dir, Options, filename:join([erlydtl_deps:get_base_dir(), "priv", "custom_tags"])),
+		  custom_tags_modules = proplists:get_value(custom_tags_modules, Options, Ctx#dtl_context.custom_tags_modules),
+		  blocktrans_fun = proplists:get_value(blocktrans_fun, Options, Ctx#dtl_context.blocktrans_fun),
+		  blocktrans_locales = proplists:get_value(blocktrans_locales, Options, Ctx#dtl_context.blocktrans_locales),
+		  vars = proplists:get_value(vars, Options, Ctx#dtl_context.vars), 
+		  reader = proplists:get_value(reader, Options, Ctx#dtl_context.reader),
+		  compiler_options = proplists:get_value(compiler_options, Options, Ctx#dtl_context.compiler_options),
+		  binary_strings = proplists:get_value(binary_strings, Options, Ctx#dtl_context.binary_strings),
+		  force_recompile = proplists:get_value(force_recompile, Options, Ctx#dtl_context.force_recompile),
+		  locale = proplists:get_value(locale, Options, Ctx#dtl_context.locale),
+		  verbose = proplists:get_value(verbose, Options, Ctx#dtl_context.verbose),
+		  is_compiling_dir = IsCompilingDir,
+		  extension_module = proplists:get_value(extension_module, Options, Ctx#dtl_context.extension_module)
+		}.
 
 init_dtl_context(File, Module, Options) when is_list(Module) ->
     init_dtl_context(File, list_to_atom(Module), Options);
@@ -275,19 +290,19 @@ is_up_to_date(CheckSum, Context) ->
             case catch Module:dependencies() of
                 L when is_list(L) ->
                     RecompileList = lists:foldl(fun
-                            ({XFile, XCheckSum}, Acc) ->
-                                case catch M:F(XFile) of
-                                    {ok, Data} ->
-                                        case binary_to_list(erlang:md5(Data)) of
-                                            XCheckSum ->
-                                                Acc;
-                                            _ ->
-                                                [recompile | Acc]
-                                        end;
-                                    _ ->
-                                        [recompile | Acc]
-                                end                                        
-                        end, [], L),
+						    ({XFile, XCheckSum}, Acc) ->
+						       case catch M:F(XFile) of
+							   {ok, Data} ->
+							       case binary_to_list(erlang:md5(Data)) of
+								   XCheckSum ->
+								       Acc;
+								   _ ->
+								       [recompile | Acc]
+							       end;
+							   _ ->
+							       [recompile | Acc]
+						       end                                        
+					       end, [], L),
                     case RecompileList of
                         [] -> true; 
                         _ -> false
@@ -298,8 +313,12 @@ is_up_to_date(CheckSum, Context) ->
         _ ->
             false
     end.
-    
-    
+
+parse(Data) ->
+    parse(Data, #dtl_context{}).
+
+parse(Data, Context) when is_binary(Data) ->
+    check_scan(erlydtl_scanner:scan(binary_to_list(Data)), Context);
 parse(File, Context) ->  
     {M, F} = Context#dtl_context.reader,
     case catch M:F(File) of
@@ -316,13 +335,13 @@ parse(File, Context) ->
         _ ->
             {error, {File, [{0, Context#dtl_context.module, "Failed to read file"}]}}
     end.
-        
+
 parse(CheckSum, Data, Context) ->
     case is_up_to_date(CheckSum, Context) of
         true ->
             ok;
         _ ->
-            case parse(Data) of
+            case parse(Data, Context) of
                 {ok, Val} ->
                     {ok, Val, CheckSum};
                 Err ->
@@ -330,13 +349,74 @@ parse(CheckSum, Data, Context) ->
             end
     end.
 
-parse(Data) ->
-    case erlydtl_scanner:scan(binary_to_list(Data)) of
-        {ok, Tokens} ->
-            erlydtl_parser:parse(Tokens);
-        Err ->
-            Err
-    end.        
+recover(undefined, _Fun, _Args) -> undefined;
+recover(Mod, Fun, Args) 
+  when is_atom(Mod), is_atom(Fun), is_list(Args) ->
+    M = case code:is_loaded(Mod) of
+	    false ->
+		case code:load_file(Mod) of
+		    {module, Mod} ->
+			Mod;
+		    _ ->
+			undefined
+		end;
+	    _ -> Mod
+	end,
+    if M /= undefined ->
+	    case erlang:function_exported(M, Fun, length(Args)) of
+		true ->
+		    apply(M, Fun, Args);
+		false ->
+		    undefined
+	    end;
+       true ->
+	    undefined
+    end.
+
+check_scan({ok, Tokens}, Context) ->
+    check_parse(erlydtl_parser:parse(Tokens), [], Context);
+check_scan({error, Err, State}, Context) ->
+    case recover(Context#dtl_context.extension_module, scan, [State]) of
+        undefined ->
+            {error, Err};
+        {ok, NewState} ->
+            %% io:format("recover from:~p~nto: ~p~n", [State, NewState]),
+            check_scan(erlydtl_scanner:resume(NewState), Context);
+        ExtRes ->
+            ExtRes
+    end.
+
+check_parse({ok, _}=Ok, [], _Context) -> Ok;
+check_parse({ok, _, _}=Ok, [], _Context) -> Ok;
+check_parse({ok, Parsed}, Acc, _Context) -> {ok, Acc ++ Parsed};
+check_parse({ok, Parsed, C}, Acc, _Context) -> {ok, Acc ++ Parsed, C};
+check_parse({error, _}=Err, _, _Context) -> Err;
+check_parse({error, Err, State}, Acc, Context) ->
+    %% io:format("parse error: ~p~nstate: ~p~n",[Err, State]),
+    {State1, Parsed} = reset_parse_state(State),
+    case recover(Context#dtl_context.extension_module, parse, [State1]) of
+        undefined ->
+            {error, Err};
+        {ok, ExtParsed} ->
+            {ok, Acc ++ Parsed ++ ExtParsed};
+        {error, ExtErr, ExtState} ->
+            case reset_parse_state(ExtState) of
+                {_, []} ->
+                    %% todo: see if this is indeed a sensible ext error,
+                    %% or if we should rather present the original Err message
+                    {error, ExtErr};
+                {State2, ExtParsed} ->
+                    check_parse(erlydtl_parser:resume(State2), Acc ++ Parsed ++ ExtParsed, Context)
+            end;
+        ExtRes ->
+            ExtRes
+    end.
+
+%% backtrack up to the Rootsymbol, and keep the current top-level value stack
+reset_parse_state([Ts, Tzr, _, [0 | []], [Parsed | []]]) ->
+    {[Ts, Tzr, 0, [], []], Parsed};
+reset_parse_state([Ts, Tzr, _, [S | Ss], [T | Stack]]) -> 
+    reset_parse_state([[T | Ts], Tzr, S, Ss, Stack]).
 
 custom_tags_ast(CustomTags, Context, TreeWalker) ->
     {{CustomTagsClauses, CustomTagsInfo}, TreeWalker1} = custom_tags_clauses_ast(CustomTags, Context, TreeWalker),
@@ -347,8 +427,8 @@ custom_tags_clauses_ast(CustomTags, Context, TreeWalker) ->
 
 custom_tags_clauses_ast1([], _ExcludeTags, ClauseAcc, InfoAcc, _Context, TreeWalker) ->
     {{lists:reverse([erl_syntax:clause([erl_syntax:variable("TagName"), erl_syntax:underscore(), erl_syntax:underscore()], none, 
-                        [erl_syntax:list([])])|ClauseAcc
-                ]), InfoAcc}, TreeWalker};
+				       [erl_syntax:list([])])|ClauseAcc
+		    ]), InfoAcc}, TreeWalker};
 custom_tags_clauses_ast1([Tag|CustomTags], ExcludeTags, ClauseAcc, InfoAcc, Context, TreeWalker) ->
     case lists:member(Tag, ExcludeTags) of
         true ->
@@ -360,101 +440,101 @@ custom_tags_clauses_ast1([Tag|CustomTags], ExcludeTags, ClauseAcc, InfoAcc, Cont
                     case parse(CustomTagFile, Context) of
                         {ok, DjangoParseTree, CheckSum} ->
                             {{BodyAst, BodyAstInfo}, TreeWalker1} = with_dependency(
-                                {CustomTagFile, CheckSum}, body_ast(DjangoParseTree, Context, TreeWalker)),
+								      {CustomTagFile, CheckSum}, body_ast(DjangoParseTree, Context, TreeWalker)),
                             MatchAst = options_match_ast(), 
                             Clause = erl_syntax:clause(
-                                [key_to_string(Tag), erl_syntax:variable("_Variables"), erl_syntax:variable("RenderOptions")],
-                                none, MatchAst ++ [BodyAst]),
+				       [key_to_string(Tag), erl_syntax:variable("_Variables"), erl_syntax:variable("RenderOptions")],
+				       none, MatchAst ++ [BodyAst]),
                             custom_tags_clauses_ast1(CustomTags, [Tag|ExcludeTags],
-                                [Clause|ClauseAcc], merge_info(BodyAstInfo, InfoAcc), 
-                                Context, TreeWalker1);
+						     [Clause|ClauseAcc], merge_info(BodyAstInfo, InfoAcc), 
+						     Context, TreeWalker1);
                         Error ->
                             throw(Error)
                     end;
                 false ->
                     custom_tags_clauses_ast1(CustomTags, [Tag | ExcludeTags],
-                        ClauseAcc, InfoAcc, Context, TreeWalker)
+					     ClauseAcc, InfoAcc, Context, TreeWalker)
             end
     end.
 
 dependencies_function(Dependencies) ->
     erl_syntax:function(
-        erl_syntax:atom(dependencies), [erl_syntax:clause([], none, 
-            [erl_syntax:list(lists:map(fun 
-                    ({XFile, XCheckSum}) -> 
-                        erl_syntax:tuple([erl_syntax:string(XFile), erl_syntax:string(XCheckSum)])
-                end, Dependencies))])]).
+      erl_syntax:atom(dependencies), [erl_syntax:clause([], none, 
+							[erl_syntax:list(lists:map(fun 
+										       ({XFile, XCheckSum}) -> 
+											  erl_syntax:tuple([erl_syntax:string(XFile), erl_syntax:string(XCheckSum)])
+										  end, Dependencies))])]).
 
 translatable_strings_function(TranslatableStrings) ->
-        erl_syntax:function(
-        erl_syntax:atom(translatable_strings), [erl_syntax:clause([], none,
-                [erl_syntax:list(lists:map(fun(String) -> 
-                                    erl_syntax:string(String) 
-                            end,
-                            TranslatableStrings))])]).
+    erl_syntax:function(
+      erl_syntax:atom(translatable_strings), [erl_syntax:clause([], none,
+								[erl_syntax:list(lists:map(fun(String) -> 
+												   erl_syntax:string(String) 
+											   end,
+											   TranslatableStrings))])]).
 
 translated_blocks_function(TranslatedBlocks) ->
-        erl_syntax:function(
-        erl_syntax:atom(translated_blocks), [erl_syntax:clause([], none,
-                [erl_syntax:list(lists:map(fun(String) -> 
-                                    erl_syntax:string(String) 
-                            end,
-                            TranslatedBlocks))])]).
+    erl_syntax:function(
+      erl_syntax:atom(translated_blocks), [erl_syntax:clause([], none,
+							     [erl_syntax:list(lists:map(fun(String) -> 
+												erl_syntax:string(String) 
+											end,
+											TranslatedBlocks))])]).
 
 variables_function(Variables) ->
-        erl_syntax:function(
-        erl_syntax:atom(variables), [erl_syntax:clause([], none,
-                [erl_syntax:list([erl_syntax:atom(S) || S <- lists:usort(Variables)])])]). 
+    erl_syntax:function(
+      erl_syntax:atom(variables), [erl_syntax:clause([], none,
+						     [erl_syntax:list([erl_syntax:atom(S) || S <- lists:usort(Variables)])])]). 
 
 custom_forms(Dir, Module, Functions, AstInfo) ->
     ModuleAst = erl_syntax:attribute(erl_syntax:atom(module), [erl_syntax:atom(Module)]),
     ExportAst = erl_syntax:attribute(erl_syntax:atom(export),
-        [erl_syntax:list([
-                    erl_syntax:arity_qualifier(erl_syntax:atom(source_dir), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(dependencies), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(translatable_strings), erl_syntax:integer(0))
-                    | 
-                        lists:foldl(fun({FunctionName, _, _}, Acc) ->
-                            [erl_syntax:arity_qualifier(erl_syntax:atom(FunctionName), erl_syntax:integer(1)),
-                                erl_syntax:arity_qualifier(erl_syntax:atom(FunctionName), erl_syntax:integer(2))|Acc]
-                    end, [], Functions)]
-            )]),
+				     [erl_syntax:list([
+						       erl_syntax:arity_qualifier(erl_syntax:atom(source_dir), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(dependencies), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(translatable_strings), erl_syntax:integer(0))
+						       | 
+						       lists:foldl(fun({FunctionName, _, _}, Acc) ->
+									   [erl_syntax:arity_qualifier(erl_syntax:atom(FunctionName), erl_syntax:integer(1)),
+									    erl_syntax:arity_qualifier(erl_syntax:atom(FunctionName), erl_syntax:integer(2))|Acc]
+								   end, [], Functions)]
+						     )]),
     SourceFunctionAst = erl_syntax:function(
-        erl_syntax:atom(source_dir), [erl_syntax:clause([], none, [erl_syntax:string(Dir)])]),
+			  erl_syntax:atom(source_dir), [erl_syntax:clause([], none, [erl_syntax:string(Dir)])]),
     DependenciesFunctionAst = dependencies_function(AstInfo#ast_info.dependencies), 
     TranslatableStringsFunctionAst = translatable_strings_function(AstInfo#ast_info.translatable_strings),
     FunctionAsts = lists:foldl(fun({_, Function1, Function2}, Acc) -> [Function1, Function2 | Acc] end, [], Functions),
 
     [erl_syntax:revert(X) || X <- [ModuleAst, ExportAst, SourceFunctionAst, DependenciesFunctionAst, TranslatableStringsFunctionAst
-            | FunctionAsts] ++ AstInfo#ast_info.pre_render_asts].
+				   | FunctionAsts] ++ AstInfo#ast_info.pre_render_asts].
 
 forms(File, Module, {BodyAst, BodyInfo}, {CustomTagsFunctionAst, CustomTagsInfo}, BinaryStrings, CheckSum) ->
     MergedInfo = merge_info(BodyInfo, CustomTagsInfo),
     Render0FunctionAst = erl_syntax:function(erl_syntax:atom(render),
-        [erl_syntax:clause([], none, [erl_syntax:application(none, 
-                        erl_syntax:atom(render), [erl_syntax:list([])])])]),
+					     [erl_syntax:clause([], none, [erl_syntax:application(none, 
+												  erl_syntax:atom(render), [erl_syntax:list([])])])]),
     Render1FunctionAst = erl_syntax:function(erl_syntax:atom(render),
-        [erl_syntax:clause([erl_syntax:variable("_Variables")], none,
-                [erl_syntax:application(none,
-                        erl_syntax:atom(render),
-                        [erl_syntax:variable("_Variables"), erl_syntax:list([])])])]),
+					     [erl_syntax:clause([erl_syntax:variable("_Variables")], none,
+								[erl_syntax:application(none,
+											erl_syntax:atom(render),
+											[erl_syntax:variable("_Variables"), erl_syntax:list([])])])]),
     Function2 = erl_syntax:application(none, erl_syntax:atom(render_internal), 
-        [erl_syntax:variable("_Variables"), erl_syntax:variable("RenderOptions")]),
+				       [erl_syntax:variable("_Variables"), erl_syntax:variable("RenderOptions")]),
     ClauseOk = erl_syntax:clause([erl_syntax:variable("Val")], none,
-        [erl_syntax:tuple([erl_syntax:atom(ok), erl_syntax:variable("Val")])]),     
+				 [erl_syntax:tuple([erl_syntax:atom(ok), erl_syntax:variable("Val")])]),     
     ClauseCatch = erl_syntax:clause([erl_syntax:variable("Err")], none,
-        [erl_syntax:tuple([erl_syntax:atom(error), erl_syntax:variable("Err")])]),            
+				    [erl_syntax:tuple([erl_syntax:atom(error), erl_syntax:variable("Err")])]),            
     Render2FunctionAst = erl_syntax:function(erl_syntax:atom(render),
-        [erl_syntax:clause([erl_syntax:variable("_Variables"),
-                    erl_syntax:variable("RenderOptions")], none, 
-            [erl_syntax:try_expr([Function2], [ClauseOk], [ClauseCatch])])]),  
-     
+					     [erl_syntax:clause([erl_syntax:variable("_Variables"),
+								 erl_syntax:variable("RenderOptions")], none, 
+								[erl_syntax:try_expr([Function2], [ClauseOk], [ClauseCatch])])]),  
+
     SourceFunctionTuple = erl_syntax:tuple(
-        [erl_syntax:string(File), erl_syntax:string(CheckSum)]),
+			    [erl_syntax:string(File), erl_syntax:string(CheckSum)]),
     SourceFunctionAst = erl_syntax:function(
-        erl_syntax:atom(source),
-            [erl_syntax:clause([], none, [SourceFunctionTuple])]),
-    
+			  erl_syntax:atom(source),
+			  [erl_syntax:clause([], none, [SourceFunctionTuple])]),
+
     DependenciesFunctionAst = dependencies_function(MergedInfo#ast_info.dependencies),
 
     TranslatableStringsAst = translatable_strings_function(MergedInfo#ast_info.translatable_strings),
@@ -464,57 +544,57 @@ forms(File, Module, {BodyAst, BodyInfo}, {CustomTagsFunctionAst, CustomTagsInfo}
     VariablesAst = variables_function(MergedInfo#ast_info.var_names),
 
     MatchAst = options_match_ast(), 
-    
+
     BodyAstTmp = MatchAst ++ [
-        erl_syntax:application(
-            erl_syntax:atom(erlydtl_runtime),
-            erl_syntax:atom(stringify_final),
-            [BodyAst, erl_syntax:atom(BinaryStrings)])
-    ],
+			      erl_syntax:application(
+				erl_syntax:atom(erlydtl_runtime),
+				erl_syntax:atom(stringify_final),
+				[BodyAst, erl_syntax:atom(BinaryStrings)])
+			     ],
 
     RenderInternalFunctionAst = erl_syntax:function(
-        erl_syntax:atom(render_internal), 
-        [erl_syntax:clause([
-            erl_syntax:variable("_Variables"),
-            erl_syntax:variable("RenderOptions")],
-            none, BodyAstTmp)]
-    ),   
-    
+				  erl_syntax:atom(render_internal), 
+				  [erl_syntax:clause([
+						      erl_syntax:variable("_Variables"),
+						      erl_syntax:variable("RenderOptions")],
+						     none, BodyAstTmp)]
+				 ),   
+
     ModuleAst  = erl_syntax:attribute(erl_syntax:atom(module), [erl_syntax:atom(Module)]),
-    
+
     ExportAst = erl_syntax:attribute(erl_syntax:atom(export),
-        [erl_syntax:list([erl_syntax:arity_qualifier(erl_syntax:atom(render), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(render), erl_syntax:integer(1)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(render), erl_syntax:integer(2)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(source), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(dependencies), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(translatable_strings), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(translated_blocks), erl_syntax:integer(0)),
-                    erl_syntax:arity_qualifier(erl_syntax:atom(variables), erl_syntax:integer(0))
-                ])]),
-    
+				     [erl_syntax:list([erl_syntax:arity_qualifier(erl_syntax:atom(render), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(render), erl_syntax:integer(1)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(render), erl_syntax:integer(2)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(source), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(dependencies), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(translatable_strings), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(translated_blocks), erl_syntax:integer(0)),
+						       erl_syntax:arity_qualifier(erl_syntax:atom(variables), erl_syntax:integer(0))
+						      ])]),
+
     [erl_syntax:revert(X) || X <- [ModuleAst, ExportAst, Render0FunctionAst, Render1FunctionAst, Render2FunctionAst,
-            SourceFunctionAst, DependenciesFunctionAst, TranslatableStringsAst,
-            TranslatedBlocksAst, VariablesAst, RenderInternalFunctionAst, 
-            CustomTagsFunctionAst | BodyInfo#ast_info.pre_render_asts]].    
+				   SourceFunctionAst, DependenciesFunctionAst, TranslatableStringsAst,
+				   TranslatedBlocksAst, VariablesAst, RenderInternalFunctionAst, 
+				   CustomTagsFunctionAst | BodyInfo#ast_info.pre_render_asts]].    
 
 options_match_ast() -> 
     [
-        erl_syntax:match_expr(
-            erl_syntax:variable("_TranslationFun"),
-            erl_syntax:application(
-                erl_syntax:atom(proplists),
-                erl_syntax:atom(get_value),
-                [erl_syntax:atom(translation_fun), erl_syntax:variable("RenderOptions"), erl_syntax:atom(none)])),
-        erl_syntax:match_expr(
-            erl_syntax:variable("_CurrentLocale"),
-            erl_syntax:application(
-                erl_syntax:atom(proplists),
-                erl_syntax:atom(get_value),
-                [erl_syntax:atom(locale), erl_syntax:variable("RenderOptions"), erl_syntax:atom(none)]))
+     erl_syntax:match_expr(
+       erl_syntax:variable("_TranslationFun"),
+       erl_syntax:application(
+	 erl_syntax:atom(proplists),
+	 erl_syntax:atom(get_value),
+	 [erl_syntax:atom(translation_fun), erl_syntax:variable("RenderOptions"), erl_syntax:atom(none)])),
+     erl_syntax:match_expr(
+       erl_syntax:variable("_CurrentLocale"),
+       erl_syntax:application(
+	 erl_syntax:atom(proplists),
+	 erl_syntax:atom(get_value),
+	 [erl_syntax:atom(locale), erl_syntax:variable("RenderOptions"), erl_syntax:atom(none)]))
     ].
-        
-% child templates should only consist of blocks at the top level
+
+						% child templates should only consist of blocks at the top level
 body_ast([{'extends', {string_literal, _Pos, String}} | ThisParseTree], Context, TreeWalker) ->
     File = full_path(unescape_string_literal(String), Context#dtl_context.doc_root),
     case lists:member(File, Context#dtl_context.parse_trail) of
@@ -524,156 +604,158 @@ body_ast([{'extends', {string_literal, _Pos, String}} | ThisParseTree], Context,
             case parse(File, Context) of
                 {ok, ParentParseTree, CheckSum} ->
                     BlockDict = lists:foldl(
-                        fun
-                            ({block, {identifier, _, Name}, Contents}, Dict) ->
-                                dict:store(Name, Contents, Dict);
-                            (_, Dict) ->
-                                Dict
-                        end, dict:new(), ThisParseTree),
+				  fun
+				      ({block, {identifier, _, Name}, Contents}, Dict) ->
+						   dict:store(Name, Contents, Dict);
+				      (_, Dict) ->
+						   Dict
+					   end, dict:new(), ThisParseTree),
                     with_dependency({File, CheckSum}, body_ast(ParentParseTree, Context#dtl_context{
-                        block_dict = dict:merge(fun(_Key, _ParentVal, ChildVal) -> ChildVal end,
-                            BlockDict, Context#dtl_context.block_dict),
-                                parse_trail = [File | Context#dtl_context.parse_trail]}, TreeWalker));
+										  block_dict = dict:merge(fun(_Key, _ParentVal, ChildVal) -> ChildVal end,
+													  BlockDict, Context#dtl_context.block_dict),
+										  parse_trail = [File | Context#dtl_context.parse_trail]}, TreeWalker));
                 Err ->
                     throw(Err)
             end        
     end;
- 
-    
+
+
 body_ast(DjangoParseTree, Context, TreeWalker) ->
     {AstInfoList, TreeWalker2} = lists:mapfoldl(
-        fun
-            ({'autoescape', {identifier, _, OnOrOff}, Contents}, TreeWalkerAcc) ->
-                body_ast(Contents, Context#dtl_context{auto_escape = OnOrOff}, 
-                    TreeWalkerAcc);
-            ({'block', {identifier, _, Name}, Contents}, TreeWalkerAcc) ->
-                Block = case dict:find(Name, Context#dtl_context.block_dict) of
-                    {ok, ChildBlock} -> ChildBlock;
-                    _ -> Contents
-                end,
-                body_ast(Block, Context, TreeWalkerAcc);
-            ({'blocktrans', Args, Contents}, TreeWalkerAcc) ->
-                blocktrans_ast(Args, Contents, Context, TreeWalkerAcc);
-            ({'call', {identifier, _, Name}}, TreeWalkerAcc) ->
-            	call_ast(Name, TreeWalkerAcc);
-            ({'call', {identifier, _, Name}, With}, TreeWalkerAcc) ->
-            	call_with_ast(Name, With, Context, TreeWalkerAcc);
-            ({'comment', _Contents}, TreeWalkerAcc) ->
-                empty_ast(TreeWalkerAcc);
-            ({'cycle', Names}, TreeWalkerAcc) ->
-                cycle_ast(Names, Context, TreeWalkerAcc);
-            ({'cycle_compat', Names}, TreeWalkerAcc) ->
-                cycle_compat_ast(Names, Context, TreeWalkerAcc);
-            ({'date', 'now', {string_literal, _Pos, FormatString}}, TreeWalkerAcc) ->
-                now_ast(FormatString, Context, TreeWalkerAcc);
-            ({'filter', FilterList, Contents}, TreeWalkerAcc) ->
-                filter_tag_ast(FilterList, Contents, Context, TreeWalkerAcc);
-            ({'firstof', Vars}, TreeWalkerAcc) ->
-                firstof_ast(Vars, Context, TreeWalkerAcc);
-            ({'for', {'in', IteratorList, Variable, Reversed}, Contents}, TreeWalkerAcc) ->
-                {EmptyAstInfo, TreeWalker1} = empty_ast(TreeWalkerAcc),
-                for_loop_ast(IteratorList, Variable, Reversed, Contents, EmptyAstInfo, Context, TreeWalker1);
-            ({'for', {'in', IteratorList, Variable, Reversed}, Contents, EmptyPartContents}, TreeWalkerAcc) ->
-                {EmptyAstInfo, TreeWalker1} = body_ast(EmptyPartContents, Context, TreeWalkerAcc),
-                for_loop_ast(IteratorList, Variable, Reversed, Contents, EmptyAstInfo, Context, TreeWalker1);
-            ({'if', Expression, Contents, Elif}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
-                {ElifAstInfo, TreeWalker2} = body_ast(Elif, Context, TreeWalker1),
-                ifelse_ast(Expression, IfAstInfo, ElifAstInfo, Context, TreeWalker2);
-            ({'if', Expression, Contents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
-                ifelse_ast(Expression, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifchanged', '$undefined', Contents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
-                ifchanged_contents_ast(Contents, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifchanged', Values, Contents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
-                ifchanged_values_ast(Values, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifchangedelse', '$undefined', IfContents, ElseContents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
-                ifchanged_contents_ast(IfContents, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifchangedelse', Values, IfContents, ElseContents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
-                ifchanged_values_ast(Values, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifelse', Expression, IfContents, ElseContents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
-                ifelse_ast(Expression, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifequal', [Arg1, Arg2], Contents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
-                ifelse_ast({'expr', "eq", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifequalelse', [Arg1, Arg2], IfContents, ElseContents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc), 
-                {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context,TreeWalker1),
-                ifelse_ast({'expr', "eq", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);                
-            ({'ifnotequal', [Arg1, Arg2], Contents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
-                ifelse_ast({'expr', "ne", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
-            ({'ifnotequalelse', [Arg1, Arg2], IfContents, ElseContents}, TreeWalkerAcc) ->
-                {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
-                {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
-                ifelse_ast({'expr', "ne", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);                    
-            ({'include', {string_literal, _, File}, Args}, TreeWalkerAcc) ->
-                include_ast(unescape_string_literal(File), Args, Context#dtl_context.local_scopes, Context, TreeWalkerAcc);
-            ({'include_only', {string_literal, _, File}, Args}, TreeWalkerAcc) ->
-                include_ast(unescape_string_literal(File), Args, [], Context, TreeWalkerAcc);
-            ({'regroup', {ListVariable, Grouper, {identifier, _, NewVariable}}, Contents}, TreeWalkerAcc) ->
-                regroup_ast(ListVariable, Grouper, NewVariable, Contents, Context, TreeWalkerAcc);
-            ({'spaceless', Contents}, TreeWalkerAcc) ->
-                spaceless_ast(Contents, Context, TreeWalkerAcc);
-            ({'ssi', Arg}, TreeWalkerAcc) ->
-                ssi_ast(Arg, Context, TreeWalkerAcc);
-            ({'ssi_parsed', {string_literal, _, FileName}}, TreeWalkerAcc) ->
-                include_ast(unescape_string_literal(FileName), [], Context#dtl_context.local_scopes, Context, TreeWalkerAcc);
-            ({'string', _Pos, String}, TreeWalkerAcc) -> 
-                string_ast(String, Context, TreeWalkerAcc);
-            ({'tag', {identifier, _, Name}, Args}, TreeWalkerAcc) ->
-                tag_ast(Name, Args, Context, TreeWalkerAcc);            
-            ({'templatetag', {_, _, TagName}}, TreeWalkerAcc) ->
-                templatetag_ast(TagName, Context, TreeWalkerAcc);
-            ({'trans', Value}, TreeWalkerAcc) ->
-                translated_ast(Value, Context, TreeWalkerAcc);
-            ({'widthratio', Numerator, Denominator, Scale}, TreeWalkerAcc) ->
-                widthratio_ast(Numerator, Denominator, Scale, Context, TreeWalkerAcc);
-            ({'with', Args, Contents}, TreeWalkerAcc) ->
-                with_ast(Args, Contents, Context, TreeWalkerAcc);
-            (ValueToken, TreeWalkerAcc) -> 
-                {{ValueAst,ValueInfo},ValueTreeWalker} = value_ast(ValueToken, true, true, Context, TreeWalkerAcc),
-                {{format(ValueAst, Context, ValueTreeWalker),ValueInfo},ValueTreeWalker}
-        end, TreeWalker, DjangoParseTree),   
+				   fun
+				       ({'autoescape', {identifier, _, OnOrOff}, Contents}, TreeWalkerAcc) ->
+						       body_ast(Contents, Context#dtl_context{auto_escape = OnOrOff}, 
+								TreeWalkerAcc);
+				       ({'block', {identifier, _, Name}, Contents}, TreeWalkerAcc) ->
+						       Block = case dict:find(Name, Context#dtl_context.block_dict) of
+								   {ok, ChildBlock} -> ChildBlock;
+								   _ -> Contents
+							       end,
+						       body_ast(Block, Context, TreeWalkerAcc);
+				       ({'blocktrans', Args, Contents}, TreeWalkerAcc) ->
+						       blocktrans_ast(Args, Contents, Context, TreeWalkerAcc);
+				       ({'call', {identifier, _, Name}}, TreeWalkerAcc) ->
+						       call_ast(Name, TreeWalkerAcc);
+				       ({'call', {identifier, _, Name}, With}, TreeWalkerAcc) ->
+						       call_with_ast(Name, With, Context, TreeWalkerAcc);
+				       ({'comment', _Contents}, TreeWalkerAcc) ->
+						       empty_ast(TreeWalkerAcc);
+				       ({'cycle', Names}, TreeWalkerAcc) ->
+						       cycle_ast(Names, Context, TreeWalkerAcc);
+				       ({'cycle_compat', Names}, TreeWalkerAcc) ->
+						       cycle_compat_ast(Names, Context, TreeWalkerAcc);
+				       ({'date', 'now', {string_literal, _Pos, FormatString}}, TreeWalkerAcc) ->
+						       now_ast(FormatString, Context, TreeWalkerAcc);
+				       ({'filter', FilterList, Contents}, TreeWalkerAcc) ->
+						       filter_tag_ast(FilterList, Contents, Context, TreeWalkerAcc);
+				       ({'firstof', Vars}, TreeWalkerAcc) ->
+						       firstof_ast(Vars, Context, TreeWalkerAcc);
+				       ({'for', {'in', IteratorList, Variable, Reversed}, Contents}, TreeWalkerAcc) ->
+						       {EmptyAstInfo, TreeWalker1} = empty_ast(TreeWalkerAcc),
+						       for_loop_ast(IteratorList, Variable, Reversed, Contents, EmptyAstInfo, Context, TreeWalker1);
+				       ({'for', {'in', IteratorList, Variable, Reversed}, Contents, EmptyPartContents}, TreeWalkerAcc) ->
+						       {EmptyAstInfo, TreeWalker1} = body_ast(EmptyPartContents, Context, TreeWalkerAcc),
+						       for_loop_ast(IteratorList, Variable, Reversed, Contents, EmptyAstInfo, Context, TreeWalker1);
+				       ({'if', Expression, Contents, Elif}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
+						       {ElifAstInfo, TreeWalker2} = body_ast(Elif, Context, TreeWalker1),
+						       ifelse_ast(Expression, IfAstInfo, ElifAstInfo, Context, TreeWalker2);
+				       ({'if', Expression, Contents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
+						       ifelse_ast(Expression, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifchanged', '$undefined', Contents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
+						       ifchanged_contents_ast(Contents, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifchanged', Values, Contents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
+						       ifchanged_values_ast(Values, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifchangedelse', '$undefined', IfContents, ElseContents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
+						       ifchanged_contents_ast(IfContents, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifchangedelse', Values, IfContents, ElseContents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
+						       ifchanged_values_ast(Values, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifelse', Expression, IfContents, ElseContents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
+						       ifelse_ast(Expression, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifequal', [Arg1, Arg2], Contents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
+						       ifelse_ast({'expr', "eq", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifequalelse', [Arg1, Arg2], IfContents, ElseContents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc), 
+						       {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context,TreeWalker1),
+						       ifelse_ast({'expr', "eq", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);                
+				       ({'ifnotequal', [Arg1, Arg2], Contents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(Contents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = empty_ast(TreeWalker1),
+						       ifelse_ast({'expr', "ne", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);
+				       ({'ifnotequalelse', [Arg1, Arg2], IfContents, ElseContents}, TreeWalkerAcc) ->
+						       {IfAstInfo, TreeWalker1} = body_ast(IfContents, Context, TreeWalkerAcc),
+						       {ElseAstInfo, TreeWalker2} = body_ast(ElseContents, Context, TreeWalker1),
+						       ifelse_ast({'expr', "ne", Arg1, Arg2}, IfAstInfo, ElseAstInfo, Context, TreeWalker2);                    
+				       ({'include', {string_literal, _, File}, Args}, TreeWalkerAcc) ->
+						       include_ast(unescape_string_literal(File), Args, Context#dtl_context.local_scopes, Context, TreeWalkerAcc);
+				       ({'include_only', {string_literal, _, File}, Args}, TreeWalkerAcc) ->
+						       include_ast(unescape_string_literal(File), Args, [], Context, TreeWalkerAcc);
+				       ({'regroup', {ListVariable, Grouper, {identifier, _, NewVariable}}, Contents}, TreeWalkerAcc) ->
+						       regroup_ast(ListVariable, Grouper, NewVariable, Contents, Context, TreeWalkerAcc);
+				       ({'spaceless', Contents}, TreeWalkerAcc) ->
+						       spaceless_ast(Contents, Context, TreeWalkerAcc);
+				       ({'ssi', Arg}, TreeWalkerAcc) ->
+						       ssi_ast(Arg, Context, TreeWalkerAcc);
+				       ({'ssi_parsed', {string_literal, _, FileName}}, TreeWalkerAcc) ->
+						       include_ast(unescape_string_literal(FileName), [], Context#dtl_context.local_scopes, Context, TreeWalkerAcc);
+				       ({'string', _Pos, String}, TreeWalkerAcc) -> 
+						       string_ast(String, Context, TreeWalkerAcc);
+				       ({'tag', {identifier, _, Name}, Args}, TreeWalkerAcc) ->
+						       tag_ast(Name, Args, Context, TreeWalkerAcc);            
+				       ({'templatetag', {_, _, TagName}}, TreeWalkerAcc) ->
+						       templatetag_ast(TagName, Context, TreeWalkerAcc);
+				       ({'trans', Value}, TreeWalkerAcc) ->
+						       translated_ast(Value, Context, TreeWalkerAcc);
+				       ({'widthratio', Numerator, Denominator, Scale}, TreeWalkerAcc) ->
+						       widthratio_ast(Numerator, Denominator, Scale, Context, TreeWalkerAcc);
+				       ({'with', Args, Contents}, TreeWalkerAcc) ->
+						       with_ast(Args, Contents, Context, TreeWalkerAcc);
+                                       ({'extension', Tag}, TreeWalkerAcc) ->
+                                           extension_ast(Tag, Context, TreeWalkerAcc);
+				       (ValueToken, TreeWalkerAcc) -> 
+						       {{ValueAst,ValueInfo},ValueTreeWalker} = value_ast(ValueToken, true, true, Context, TreeWalkerAcc),
+						       {{format(ValueAst, Context, ValueTreeWalker),ValueInfo},ValueTreeWalker}
+					       end, TreeWalker, DjangoParseTree),   
     {AstList, {Info, TreeWalker3}} = lists:mapfoldl(
-        fun({Ast, Info}, {InfoAcc, TreeWalkerAcc}) -> 
-                PresetVars = lists:foldl(fun
-                        (X, Acc) ->
-                            case proplists:lookup(X, Context#dtl_context.vars) of
-                                none ->
-                                    Acc;
-                                Val ->
-                                    [erl_syntax:abstract(Val) | Acc]
-                            end
-                    end, [], Info#ast_info.var_names),
-                case PresetVars of
-                    [] ->
-                        {Ast, {merge_info(Info, InfoAcc), TreeWalkerAcc}};
-                    _ ->
-                        Counter = TreeWalkerAcc#treewalker.counter,
-                        Name = lists:concat([pre_render, Counter]),
-                        Ast1 = erl_syntax:application(none, erl_syntax:atom(Name),
-                            [erl_syntax:list(PresetVars)]),
-                        PreRenderAst = erl_syntax:function(erl_syntax:atom(Name),
-                            [erl_syntax:clause([erl_syntax:variable("_Variables")], none, [Ast])]),
-                        PreRenderAsts = Info#ast_info.pre_render_asts,
-                        Info1 = Info#ast_info{pre_render_asts = [PreRenderAst | PreRenderAsts]},     
-                        {Ast1, {merge_info(Info1, InfoAcc), TreeWalkerAcc#treewalker{counter = Counter + 1}}}
-                end
-        end, {#ast_info{}, TreeWalker2}, AstInfoList),
+				       fun({Ast, Info}, {InfoAcc, TreeWalkerAcc}) -> 
+					       PresetVars = lists:foldl(fun
+									    (X, Acc) ->
+									       case proplists:lookup(X, Context#dtl_context.vars) of
+										   none ->
+										       Acc;
+										   Val ->
+										       [erl_syntax:abstract(Val) | Acc]
+									       end
+								       end, [], Info#ast_info.var_names),
+					       case PresetVars of
+						   [] ->
+						       {Ast, {merge_info(Info, InfoAcc), TreeWalkerAcc}};
+						   _ ->
+						       Counter = TreeWalkerAcc#treewalker.counter,
+						       Name = lists:concat([pre_render, Counter]),
+						       Ast1 = erl_syntax:application(none, erl_syntax:atom(Name),
+										     [erl_syntax:list(PresetVars)]),
+						       PreRenderAst = erl_syntax:function(erl_syntax:atom(Name),
+											  [erl_syntax:clause([erl_syntax:variable("_Variables")], none, [Ast])]),
+						       PreRenderAsts = Info#ast_info.pre_render_asts,
+						       Info1 = Info#ast_info{pre_render_asts = [PreRenderAst | PreRenderAsts]},     
+						       {Ast1, {merge_info(Info1, InfoAcc), TreeWalkerAcc#treewalker{counter = Counter + 1}}}
+					       end
+				       end, {#ast_info{}, TreeWalker2}, AstInfoList),
     {{erl_syntax:list(AstList), Info}, TreeWalker3}.
 
 
@@ -709,38 +791,46 @@ value_ast(ValueToken, AsString, EmptyIfUndefined, Context, TreeWalker) ->
             {{Ast, #ast_info{var_names = [VarName]}}, TreeWalker}
     end.
 
+extension_ast(Tag, Context, TreeWalker) ->
+    case recover(Context#dtl_context.extension_module, compile_ast, [Tag, Context, TreeWalker]) of
+        undefined ->
+            throw({error, {unknown_extension, Tag}});
+        Result ->
+            Result
+    end.
+
 merge_info(Info1, Info2) ->
     #ast_info{
-        dependencies = 
-            lists:merge(
-                lists:sort(Info1#ast_info.dependencies), 
-                lists:sort(Info2#ast_info.dependencies)),
-        var_names = 
-            lists:merge(
-                lists:sort(Info1#ast_info.var_names), 
-                lists:sort(Info2#ast_info.var_names)),
-        translatable_strings =
-            lists:merge(
-                lists:sort(Info1#ast_info.translatable_strings),
-                lists:sort(Info2#ast_info.translatable_strings)),
-        translated_blocks =
-            lists:merge(
-                lists:sort(Info1#ast_info.translated_blocks),
-                lists:sort(Info2#ast_info.translated_blocks)),
-        custom_tags = 
-            lists:merge(
-                lists:sort(Info1#ast_info.custom_tags),
-                lists:sort(Info2#ast_info.custom_tags)),
-        pre_render_asts = 
-            lists:merge(
-                Info1#ast_info.pre_render_asts,
-                Info2#ast_info.pre_render_asts)}.
+	    dependencies = 
+		lists:merge(
+		  lists:sort(Info1#ast_info.dependencies), 
+		  lists:sort(Info2#ast_info.dependencies)),
+	    var_names = 
+		lists:merge(
+		  lists:sort(Info1#ast_info.var_names), 
+		  lists:sort(Info2#ast_info.var_names)),
+	    translatable_strings =
+		lists:merge(
+		  lists:sort(Info1#ast_info.translatable_strings),
+		  lists:sort(Info2#ast_info.translatable_strings)),
+	    translated_blocks =
+		lists:merge(
+		  lists:sort(Info1#ast_info.translated_blocks),
+		  lists:sort(Info2#ast_info.translated_blocks)),
+	    custom_tags = 
+		lists:merge(
+		  lists:sort(Info1#ast_info.custom_tags),
+		  lists:sort(Info2#ast_info.custom_tags)),
+	    pre_render_asts = 
+		lists:merge(
+		  Info1#ast_info.pre_render_asts,
+		  Info2#ast_info.pre_render_asts)}.
 
 
 with_dependencies([], Args) ->
     Args;
 with_dependencies([Dependency | Rest], Args) ->
-     with_dependencies(Rest, with_dependency(Dependency, Args)).
+    with_dependencies(Rest, with_dependency(Dependency, Args)).
 
 with_dependency(FilePath, {{Ast, Info}, TreeWalker}) ->
     {{Ast, Info#ast_info{dependencies = [FilePath | Info#ast_info.dependencies]}}, TreeWalker}.
@@ -751,10 +841,10 @@ empty_ast(TreeWalker) ->
 
 blocktrans_ast(ArgList, Contents, Context, TreeWalker) ->
     {NewScope, {ArgInfo, TreeWalker1}} = lists:mapfoldl(fun
-            ({{identifier, _, LocalVarName}, Value}, {AstInfo1, TreeWalker1}) ->
-                {{Ast, Info}, TreeWalker2} = value_ast(Value, false, false, Context, TreeWalker1),
-                {{LocalVarName, Ast}, {merge_info(AstInfo1, Info), TreeWalker2}}
-        end, {#ast_info{}, TreeWalker}, ArgList),
+							    ({{identifier, _, LocalVarName}, Value}, {AstInfo1, TreeWalker1}) ->
+							       {{Ast, Info}, TreeWalker2} = value_ast(Value, false, false, Context, TreeWalker1),
+							       {{LocalVarName, Ast}, {merge_info(AstInfo1, Info), TreeWalker2}}
+						       end, {#ast_info{}, TreeWalker}, ArgList),
     NewContext = Context#dtl_context{ local_scopes = [NewScope|Context#dtl_context.local_scopes] },
     SourceText = lists:flatten(erlydtl_unparser:unparse(Contents)),
     {{DefaultAst, AstInfo}, TreeWalker2} = body_ast(Contents, NewContext, TreeWalker1),
@@ -764,41 +854,41 @@ blocktrans_ast(ArgList, Contents, Context, TreeWalker) ->
             {{DefaultAst, MergedInfo}, TreeWalker2};
         BlockTransFun when is_function(BlockTransFun) ->
             {FinalAstInfo, FinalTreeWalker, Clauses} = lists:foldr(fun(Locale, {AstInfoAcc, ThisTreeWalker, ClauseAcc}) ->
-                        case BlockTransFun(SourceText, Locale) of
-                            default ->
-                                {AstInfoAcc, ThisTreeWalker, ClauseAcc};
-                            Body ->
-                                {ok, DjangoParseTree} = parse(Body),
-                                {{ThisAst, ThisAstInfo}, TreeWalker3} = body_ast(DjangoParseTree, NewContext, ThisTreeWalker),
-                                {merge_info(ThisAstInfo, AstInfoAcc), TreeWalker3, 
-                                    [erl_syntax:clause([erl_syntax:string(Locale)], none, [ThisAst])|ClauseAcc]}
-                        end
-                end, {MergedInfo, TreeWalker2, []}, Context#dtl_context.blocktrans_locales),
+									   case BlockTransFun(SourceText, Locale) of
+									       default ->
+										   {AstInfoAcc, ThisTreeWalker, ClauseAcc};
+									       Body ->
+										   {ok, DjangoParseTree} = parse(Body, Context),
+										   {{ThisAst, ThisAstInfo}, TreeWalker3} = body_ast(DjangoParseTree, NewContext, ThisTreeWalker),
+										   {merge_info(ThisAstInfo, AstInfoAcc), TreeWalker3, 
+										    [erl_syntax:clause([erl_syntax:string(Locale)], none, [ThisAst])|ClauseAcc]}
+									   end
+								   end, {MergedInfo, TreeWalker2, []}, Context#dtl_context.blocktrans_locales),
             Ast = erl_syntax:case_expr(erl_syntax:variable("_CurrentLocale"),
-                Clauses ++ [erl_syntax:clause([erl_syntax:underscore()], none, [DefaultAst])]),
+				       Clauses ++ [erl_syntax:clause([erl_syntax:underscore()], none, [DefaultAst])]),
             {{Ast, FinalAstInfo#ast_info{ translated_blocks = [SourceText] }}, FinalTreeWalker}
     end.
 
 translated_ast({string_literal, _, String}, Context, TreeWalker) ->
     NewStr = unescape_string_literal(String),
     DefaultString = case Context#dtl_context.locale of
-        none -> NewStr;
-        Locale -> erlydtl_i18n:translate(NewStr,Locale)
-    end,
+			none -> NewStr;
+			Locale -> erlydtl_i18n:translate(NewStr,Locale)
+		    end,
     translated_ast2(erl_syntax:string(NewStr), erl_syntax:string(DefaultString), 
-        #ast_info{translatable_strings = [NewStr]}, TreeWalker);
+		    #ast_info{translatable_strings = [NewStr]}, TreeWalker);
 translated_ast(ValueToken, Context, TreeWalker) ->
     {{Ast, Info}, TreeWalker1} = value_ast(ValueToken, true, false, Context, TreeWalker),
     translated_ast2(Ast, Ast, Info, TreeWalker1).
 
 translated_ast2(NewStrAst, DefaultStringAst, AstInfo, TreeWalker) ->
     StringLookupAst = erl_syntax:application(
-        erl_syntax:atom(erlydtl_runtime),
-        erl_syntax:atom(translate),
-        [NewStrAst, erl_syntax:variable("_TranslationFun"), DefaultStringAst]),
+			erl_syntax:atom(erlydtl_runtime),
+			erl_syntax:atom(translate),
+			[NewStrAst, erl_syntax:variable("_TranslationFun"), DefaultStringAst]),
     {{StringLookupAst, AstInfo}, TreeWalker}.
 
-% Completely unnecessary in ErlyDTL (use {{ "{%" }} etc), but implemented for compatibility.
+						% Completely unnecessary in ErlyDTL (use {{ "{%" }} etc), but implemented for compatibility.
 templatetag_ast("openblock", Context, TreeWalker) ->
     string_ast("{%", Context, TreeWalker);
 templatetag_ast("closeblock", Context, TreeWalker) ->
@@ -822,10 +912,10 @@ widthratio_ast(Numerator, Denominator, Scale, Context, TreeWalker) ->
     {{DenAst, DenInfo}, TreeWalker2} = value_ast(Denominator, false, true, Context, TreeWalker1),
     {{ScaleAst, ScaleInfo}, TreeWalker3} = value_ast(Scale, false, true, Context, TreeWalker2),
     {{format_number_ast(erl_syntax:application(
-                erl_syntax:atom(erlydtl_runtime),
-                erl_syntax:atom(widthratio),
-                [NumAst, DenAst, ScaleAst])), merge_info(ScaleInfo, merge_info(NumInfo, DenInfo))},
-        TreeWalker3}.
+			  erl_syntax:atom(erlydtl_runtime),
+			  erl_syntax:atom(widthratio),
+			  [NumAst, DenAst, ScaleAst])), merge_info(ScaleInfo, merge_info(NumInfo, DenInfo))},
+     TreeWalker3}.
 
 binary_string(String) ->
     erl_syntax:binary([erl_syntax:binary_field(erl_syntax:integer(X)) || X <- String]).
@@ -843,57 +933,57 @@ include_ast(File, ArgList, Scopes, Context, TreeWalker) ->
     case parse(FilePath, Context) of
         {ok, InclusionParseTree, CheckSum} ->
             {NewScope, {ArgInfo, TreeWalker1}} = lists:mapfoldl(fun
-                    ({{identifier, _, LocalVarName}, Value}, {AstInfo1, TreeWalker1}) ->
-                        {{Ast, Info}, TreeWalker2} = value_ast(Value, false, false, Context, TreeWalker1),
-                        {{LocalVarName, Ast}, {merge_info(AstInfo1, Info), TreeWalker2}}
-                end, {#ast_info{}, TreeWalker}, ArgList),
+								    ({{identifier, _, LocalVarName}, Value}, {AstInfo1, TreeWalker1}) ->
+								       {{Ast, Info}, TreeWalker2} = value_ast(Value, false, false, Context, TreeWalker1),
+								       {{LocalVarName, Ast}, {merge_info(AstInfo1, Info), TreeWalker2}}
+							       end, {#ast_info{}, TreeWalker}, ArgList),
 
             {{BodyAst, BodyInfo}, TreeWalker2} = with_dependency({FilePath, CheckSum}, 
-                body_ast(InclusionParseTree, Context#dtl_context{
-                        parse_trail = [FilePath | Context#dtl_context.parse_trail],
-                        local_scopes = [NewScope|Scopes]
-                    }, TreeWalker1)),
+								 body_ast(InclusionParseTree, Context#dtl_context{
+												parse_trail = [FilePath | Context#dtl_context.parse_trail],
+												local_scopes = [NewScope|Scopes]
+											       }, TreeWalker1)),
 
             {{BodyAst, merge_info(BodyInfo, ArgInfo)}, TreeWalker2};
         Err ->
             throw(Err)
     end.
-    
-% include at run-time
+
+						% include at run-time
 ssi_ast(FileName, Context, TreeWalker) ->
     {{Ast, Info}, TreeWalker1} = value_ast(FileName, true, true, Context, TreeWalker),
     {Mod, Fun} = Context#dtl_context.reader,
     {{erl_syntax:application(
-                erl_syntax:atom(erlydtl_runtime),
-                erl_syntax:atom(read_file),
-                [erl_syntax:atom(Mod), erl_syntax:atom(Fun), erl_syntax:string(Context#dtl_context.doc_root), Ast]), Info}, TreeWalker1}.
+	erl_syntax:atom(erlydtl_runtime),
+	erl_syntax:atom(read_file),
+	[erl_syntax:atom(Mod), erl_syntax:atom(Fun), erl_syntax:string(Context#dtl_context.doc_root), Ast]), Info}, TreeWalker1}.
 
 filter_tag_ast(FilterList, Contents, Context, TreeWalker) ->
     {{InnerAst, Info}, TreeWalker1} = body_ast(Contents, Context#dtl_context{auto_escape = did}, TreeWalker),
     {{FilteredAst, FilteredInfo}, TreeWalker2} = lists:foldl(fun
-            ([{identifier, _, 'escape'}], {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
-                {{AstAcc, InfoAcc}, TreeWalkerAcc#treewalker{safe = true}};
-            ([{identifier, _, 'safe'}], {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
-                {{AstAcc, InfoAcc}, TreeWalkerAcc#treewalker{safe = true}};
-            ([{identifier, _, 'safeseq'}], {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
-                {{AstAcc, InfoAcc}, TreeWalkerAcc#treewalker{safe = true}};
-            (Filter, {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
-                {Ast, AstInfo} = filter_ast1(Filter, AstAcc, Context),
-                {{Ast, merge_info(InfoAcc, AstInfo)}, TreeWalkerAcc}
-        end, {{erl_syntax:application(
-                    erl_syntax:atom(erlang),
-                    erl_syntax:atom(iolist_to_binary),
-                    [InnerAst]), Info}, TreeWalker1}, FilterList),
+								 ([{identifier, _, 'escape'}], {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
+								    {{AstAcc, InfoAcc}, TreeWalkerAcc#treewalker{safe = true}};
+								 ([{identifier, _, 'safe'}], {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
+								    {{AstAcc, InfoAcc}, TreeWalkerAcc#treewalker{safe = true}};
+								 ([{identifier, _, 'safeseq'}], {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
+								    {{AstAcc, InfoAcc}, TreeWalkerAcc#treewalker{safe = true}};
+								 (Filter, {{AstAcc, InfoAcc}, TreeWalkerAcc}) ->
+								    {Ast, AstInfo} = filter_ast1(Filter, AstAcc, Context),
+								    {{Ast, merge_info(InfoAcc, AstInfo)}, TreeWalkerAcc}
+							    end, {{erl_syntax:application(
+								     erl_syntax:atom(erlang),
+								     erl_syntax:atom(iolist_to_binary),
+								     [InnerAst]), Info}, TreeWalker1}, FilterList),
 
     EscapedAst = case search_for_escape_filter(lists:reverse(FilterList), Context) of
-        on ->
-            erl_syntax:application(
-                erl_syntax:atom(erlydtl_filters), 
-                erl_syntax:atom(force_escape), 
-                [FilteredAst]);
-        _ ->
-            FilteredAst
-    end,
+		     on ->
+			 erl_syntax:application(
+			   erl_syntax:atom(erlydtl_filters), 
+			   erl_syntax:atom(force_escape), 
+			   [FilteredAst]);
+		     _ ->
+			 FilteredAst
+		 end,
     {{EscapedAst, FilteredInfo}, TreeWalker2}.
 
 search_for_escape_filter(FilterList, #dtl_context{auto_escape = on}) ->
@@ -917,21 +1007,21 @@ search_for_safe_filter([]) ->
     on.
 
 filter_ast(Variable, Filter, Context, TreeWalker) ->
-    % the escape filter is special; it is always applied last, so we have to go digging for it
+						% the escape filter is special; it is always applied last, so we have to go digging for it
 
-    % AutoEscape = 'did' means we (will have) decided whether to escape the current variable,
-    % so don't do any more escaping
+						% AutoEscape = 'did' means we (will have) decided whether to escape the current variable,
+						% so don't do any more escaping
     {{UnescapedAst, Info}, TreeWalker2} = filter_ast_noescape(Variable, Filter, 
-        Context#dtl_context{auto_escape = did}, TreeWalker),
+							      Context#dtl_context{auto_escape = did}, TreeWalker),
     EscapedAst = case search_for_escape_filter(Variable, Filter, Context) of
-        on ->
-            erl_syntax:application(
-                erl_syntax:atom(erlydtl_filters), 
-                erl_syntax:atom(force_escape), 
-                [UnescapedAst]);
-        _ -> 
-            UnescapedAst
-    end,
+		     on ->
+			 erl_syntax:application(
+			   erl_syntax:atom(erlydtl_filters), 
+			   erl_syntax:atom(force_escape), 
+			   [UnescapedAst]);
+		     _ -> 
+			 UnescapedAst
+		 end,
     {{EscapedAst, Info}, TreeWalker2}.
 
 filter_ast_noescape(Variable, [{identifier, _, 'escape'}], Context, TreeWalker) ->
@@ -961,7 +1051,7 @@ filter_ast2(Name, VariableAst, [], VarNames, #dtl_context{ filter_modules = [Mod
     case lists:member({Name, 1}, Module:module_info(exports)) of
         true ->
             {erl_syntax:application(erl_syntax:atom(Module), erl_syntax:atom(Name), 
-                    [VariableAst]), #ast_info{var_names = VarNames}};
+				    [VariableAst]), #ast_info{var_names = VarNames}};
         false ->
             filter_ast2(Name, VariableAst, [], VarNames, Context#dtl_context{ filter_modules = Rest })
     end;
@@ -969,11 +1059,11 @@ filter_ast2(Name, VariableAst, [Arg], VarNames, #dtl_context{ filter_modules = [
     case lists:member({Name, 2}, Module:module_info(exports)) of
         true ->
             {erl_syntax:application(erl_syntax:atom(Module), erl_syntax:atom(Name),
-                    [VariableAst, Arg]), #ast_info{var_names = VarNames}};
+				    [VariableAst, Arg]), #ast_info{var_names = VarNames}};
         false ->
             filter_ast2(Name, VariableAst, [Arg], VarNames, Context#dtl_context{ filter_modules = Rest })
     end.
- 
+
 search_for_escape_filter(Variable, Filter, #dtl_context{auto_escape = on}) ->
     search_for_safe_filter(Variable, Filter);
 search_for_escape_filter(_, _, #dtl_context{auto_escape = did}) ->
@@ -998,51 +1088,51 @@ resolve_variable_ast(VarTuple, Context, true) ->
     resolve_variable_ast1(VarTuple, Context, 'fetch_value');
 resolve_variable_ast(VarTuple, Context, false) ->
     resolve_variable_ast1(VarTuple, Context, 'find_value').
- 
+
 resolve_variable_ast1({attribute, {{identifier, {Row, Col}, AttrName}, Variable}}, Context, FinderFunction) ->
     {VarAst, VarName} = resolve_variable_ast1(Variable, Context, FinderFunction),
     FileNameAst = case Context#dtl_context.parse_trail of 
-        [] -> erl_syntax:atom(undefined); 
-        [H|_] -> erl_syntax:string(H)
-    end,
+		      [] -> erl_syntax:atom(undefined); 
+		      [H|_] -> erl_syntax:string(H)
+		  end,
     {erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(FinderFunction),
-                    [erl_syntax:atom(AttrName), VarAst, FileNameAst,
-                        erl_syntax:tuple([erl_syntax:integer(Row), erl_syntax:integer(Col)])
-                    ]), VarName};
+			    [erl_syntax:atom(AttrName), VarAst, FileNameAst,
+			     erl_syntax:tuple([erl_syntax:integer(Row), erl_syntax:integer(Col)])
+			    ]), VarName};
 
 resolve_variable_ast1({variable, {identifier, {Row, Col}, VarName}}, Context, FinderFunction) ->
     VarValue = case resolve_scoped_variable_ast(VarName, Context) of
-        undefined ->
-            FileNameAst = case Context#dtl_context.parse_trail of 
-                [] -> erl_syntax:atom(undefined); 
-                [H|_] -> erl_syntax:string(H)
-            end,
-            erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(FinderFunction),
-                [erl_syntax:atom(VarName), erl_syntax:variable("_Variables"), FileNameAst,
-                    erl_syntax:tuple([erl_syntax:integer(Row), erl_syntax:integer(Col)])
-                ]);
-        Val ->
-            Val
-    end,
+		   undefined ->
+		       FileNameAst = case Context#dtl_context.parse_trail of 
+					 [] -> erl_syntax:atom(undefined); 
+					 [H|_] -> erl_syntax:string(H)
+				     end,
+		       erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(FinderFunction),
+					      [erl_syntax:atom(VarName), erl_syntax:variable("_Variables"), FileNameAst,
+					       erl_syntax:tuple([erl_syntax:integer(Row), erl_syntax:integer(Col)])
+					      ]);
+		   Val ->
+		       Val
+	       end,
     {VarValue, VarName};
 
 resolve_variable_ast1(What, _Context, _FinderFunction) ->
-   error_logger:error_msg("~p:resolve_variable_ast unhandled: ~p~n", [?MODULE, What]).
+    error_logger:error_msg("~p:resolve_variable_ast unhandled: ~p~n", [?MODULE, What]).
 
 resolve_scoped_variable_ast(VarName, Context) ->
     lists:foldl(fun(Scope, Value) ->
-                case Value of
-                    undefined -> proplists:get_value(VarName, Scope);
-                    _ -> Value
-                end
-        end, undefined, Context#dtl_context.local_scopes).
+			case Value of
+			    undefined -> proplists:get_value(VarName, Scope);
+			    _ -> Value
+			end
+		end, undefined, Context#dtl_context.local_scopes).
 
 format(Ast, Context, TreeWalker) ->
     auto_escape(format_number_ast(Ast), Context, TreeWalker).
 
 format_number_ast(Ast) ->
     erl_syntax:application(erl_syntax:atom(erlydtl_filters), erl_syntax:atom(format_number),
-        [Ast]).
+			   [Ast]).
 
 
 auto_escape(Value, _, #treewalker{safe = true}) ->
@@ -1053,59 +1143,59 @@ auto_escape(Value, _, _) ->
     Value.
 
 firstof_ast(Vars, Context, TreeWalker) ->
-	body_ast([lists:foldr(fun
-        ({L, _, _}=Var, []) when L=:=string_literal;L=:=number_literal ->
-            Var;
-        ({L, _, _}, _) when L=:=string_literal;L=:=number_literal ->
-            erlang:error(errbadliteral);
-        (Var, []) ->
-            {'ifelse', Var, [Var], []};
-        (Var, Acc) ->
-            {'ifelse', Var, [Var], [Acc]} end,
-    	[], Vars)], Context, TreeWalker).
+    body_ast([lists:foldr(fun
+			      ({L, _, _}=Var, []) when L=:=string_literal;L=:=number_literal ->
+				 Var;
+			      ({L, _, _}, _) when L=:=string_literal;L=:=number_literal ->
+				 erlang:error(errbadliteral);
+			      (Var, []) ->
+				 {'ifelse', Var, [Var], []};
+			      (Var, Acc) ->
+				 {'ifelse', Var, [Var], [Acc]} end,
+			  [], Vars)], Context, TreeWalker).
 
 ifelse_ast(Expression, {IfContentsAst, IfContentsInfo}, {ElseContentsAst, ElseContentsInfo}, Context, TreeWalker) ->
     Info = merge_info(IfContentsInfo, ElseContentsInfo),
     {{Ast, ExpressionInfo}, TreeWalker1} = value_ast(Expression, false, false, Context, TreeWalker), 
     {{erl_syntax:case_expr(erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(is_true), [Ast]),
-        [erl_syntax:clause([erl_syntax:atom(true)], none, 
-                [IfContentsAst]),
-            erl_syntax:clause([erl_syntax:underscore()], none,
-                [ElseContentsAst])
-        ]), merge_info(ExpressionInfo, Info)}, TreeWalker1}.
+			   [erl_syntax:clause([erl_syntax:atom(true)], none, 
+					      [IfContentsAst]),
+			    erl_syntax:clause([erl_syntax:underscore()], none,
+					      [ElseContentsAst])
+			   ]), merge_info(ExpressionInfo, Info)}, TreeWalker1}.
 
 with_ast(ArgList, Contents, Context, TreeWalker) ->
     {ArgAstList, {ArgInfo, TreeWalker1}} = lists:mapfoldl(fun
-            ({{identifier, _, _LocalVarName}, Value}, {AstInfo1, TreeWalker1}) ->
-                {{Ast, Info}, TreeWalker2} = value_ast(Value, false, false, Context, TreeWalker1),
-                {Ast, {merge_info(AstInfo1, Info), TreeWalker2}}
-        end, {#ast_info{}, TreeWalker}, ArgList),
+							      ({{identifier, _, _LocalVarName}, Value}, {AstInfo1, TreeWalker1}) ->
+								 {{Ast, Info}, TreeWalker2} = value_ast(Value, false, false, Context, TreeWalker1),
+								 {Ast, {merge_info(AstInfo1, Info), TreeWalker2}}
+							 end, {#ast_info{}, TreeWalker}, ArgList),
 
     NewScope = lists:map(fun({{identifier, _, LocalVarName}, _Value}) ->
-                    {LocalVarName, erl_syntax:variable(lists:concat(["Var_", LocalVarName]))}
-            end, ArgList),
+				 {LocalVarName, erl_syntax:variable(lists:concat(["Var_", LocalVarName]))}
+			 end, ArgList),
 
     {{InnerAst, InnerInfo}, TreeWalker2} = body_ast(Contents,
-        Context#dtl_context{local_scopes = [NewScope|Context#dtl_context.local_scopes]}, TreeWalker1),
+						    Context#dtl_context{local_scopes = [NewScope|Context#dtl_context.local_scopes]}, TreeWalker1),
 
     {{erl_syntax:application(
-                erl_syntax:fun_expr([
-                        erl_syntax:clause(lists:map(fun({_, Var}) -> Var end, NewScope), none,
-                            [InnerAst])]), ArgAstList), merge_info(ArgInfo, InnerInfo)}, TreeWalker2}.
+	erl_syntax:fun_expr([
+			     erl_syntax:clause(lists:map(fun({_, Var}) -> Var end, NewScope), none,
+					       [InnerAst])]), ArgAstList), merge_info(ArgInfo, InnerInfo)}, TreeWalker2}.
 
 regroup_ast(ListVariable, GrouperVariable, LocalVarName, Contents, Context, TreeWalker) ->
     {{ListAst, ListInfo}, TreeWalker1} = value_ast(ListVariable, false, true, Context, TreeWalker),
     NewScope = [{LocalVarName, erl_syntax:variable(lists:concat(["Var_", LocalVarName]))}],
 
     {{InnerAst, InnerInfo}, TreeWalker2} = body_ast(Contents, 
-        Context#dtl_context{ local_scopes = [NewScope|Context#dtl_context.local_scopes] }, TreeWalker1),
+						    Context#dtl_context{ local_scopes = [NewScope|Context#dtl_context.local_scopes] }, TreeWalker1),
 
     Ast = {erl_syntax:application(
-                erl_syntax:fun_expr([
-                        erl_syntax:clause([erl_syntax:variable(lists:concat(["Var_", LocalVarName]))], none,
-                            [InnerAst])]), 
-                [erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(regroup),
-                        [ListAst, regroup_filter(GrouperVariable,[])])]), merge_info(ListInfo, InnerInfo)},
+	     erl_syntax:fun_expr([
+				  erl_syntax:clause([erl_syntax:variable(lists:concat(["Var_", LocalVarName]))], none,
+						    [InnerAst])]), 
+	     [erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(regroup),
+				     [ListAst, regroup_filter(GrouperVariable,[])])]), merge_info(ListInfo, InnerInfo)},
     {Ast,TreeWalker2}.
 
 regroup_filter({attribute,{{identifier,_,Ident},Next}},Acc) ->
@@ -1116,52 +1206,52 @@ regroup_filter({variable,{identifier,_,Var}},Acc) ->
 
 for_loop_ast(IteratorList, LoopValue, IsReversed, Contents, {EmptyContentsAst, EmptyContentsInfo}, Context, TreeWalker) ->
     Vars = lists:map(fun({identifier, _, Iterator}) -> 
-                erl_syntax:variable(lists:concat(["Var_", Iterator])) 
-            end, IteratorList),
+			     erl_syntax:variable(lists:concat(["Var_", Iterator])) 
+		     end, IteratorList),
     {{InnerAst, Info}, TreeWalker1} = body_ast(Contents,
-        Context#dtl_context{local_scopes = [
-                [{'forloop', erl_syntax:variable("Counters")} | lists:map(
-                    fun({identifier, _, Iterator}) ->
-                            {Iterator, erl_syntax:variable(lists:concat(["Var_", Iterator]))} 
-                    end, IteratorList)] | Context#dtl_context.local_scopes]}, TreeWalker),
+					       Context#dtl_context{local_scopes = [
+										   [{'forloop', erl_syntax:variable("Counters")} | lists:map(
+																     fun({identifier, _, Iterator}) ->
+																	     {Iterator, erl_syntax:variable(lists:concat(["Var_", Iterator]))} 
+																     end, IteratorList)] | Context#dtl_context.local_scopes]}, TreeWalker),
     CounterAst = erl_syntax:application(erl_syntax:atom(erlydtl_runtime), 
-        erl_syntax:atom(increment_counter_stats), [erl_syntax:variable("Counters")]),
+					erl_syntax:atom(increment_counter_stats), [erl_syntax:variable("Counters")]),
 
     {{LoopValueAst, LoopValueInfo}, TreeWalker2} = value_ast(LoopValue, false, true, Context, TreeWalker1),
 
     LoopValueAst0 = case IsReversed of
-        true -> erl_syntax:application(erl_syntax:atom(lists), erl_syntax:atom(reverse), [LoopValueAst]);
-        false -> LoopValueAst
-    end,
+			true -> erl_syntax:application(erl_syntax:atom(lists), erl_syntax:atom(reverse), [LoopValueAst]);
+			false -> LoopValueAst
+		    end,
 
     CounterVars0 = case resolve_scoped_variable_ast('forloop', Context) of
-        undefined ->
-            erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(init_counter_stats), [LoopValueAst0]);
-        Value ->
-            erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(init_counter_stats), [LoopValueAst0, Value])
-    end,
+		       undefined ->
+			   erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(init_counter_stats), [LoopValueAst0]);
+		       Value ->
+			   erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(init_counter_stats), [LoopValueAst0, Value])
+		   end,
     {{erl_syntax:case_expr(
-                erl_syntax:application(
-                    erl_syntax:atom('erlydtl_runtime'), erl_syntax:atom('forloop'),
-                    [erl_syntax:fun_expr([
+	erl_syntax:application(
+	  erl_syntax:atom('erlydtl_runtime'), erl_syntax:atom('forloop'),
+	  [erl_syntax:fun_expr([
                                 erl_syntax:clause([erl_syntax:tuple(Vars), erl_syntax:variable("Counters")], none, 
-                                    [erl_syntax:tuple([InnerAst, CounterAst])]),
+						  [erl_syntax:tuple([InnerAst, CounterAst])]),
                                 erl_syntax:clause(case Vars of [H] -> [H, erl_syntax:variable("Counters")];
-                                        _ -> [erl_syntax:list(Vars), erl_syntax:variable("Counters")] end, none, 
-                                    [erl_syntax:tuple([InnerAst, CounterAst])])
-                            ]),
-                        CounterVars0, LoopValueAst0]),
-                [erl_syntax:clause(
-                        [erl_syntax:tuple([erl_syntax:underscore(), 
-                                    erl_syntax:list([erl_syntax:tuple([erl_syntax:atom(counter), erl_syntax:integer(1)])], 
-                                        erl_syntax:underscore())])],
-                        none, [EmptyContentsAst]),
-                    erl_syntax:clause(
-                        [erl_syntax:tuple([erl_syntax:variable("L"), erl_syntax:underscore()])],
-                        none, [erl_syntax:variable("L")])]
-            ),
-            merge_info(merge_info(Info, EmptyContentsInfo), LoopValueInfo)
-        }, TreeWalker2}.
+						      _ -> [erl_syntax:list(Vars), erl_syntax:variable("Counters")] end, none, 
+						  [erl_syntax:tuple([InnerAst, CounterAst])])
+			       ]),
+	   CounterVars0, LoopValueAst0]),
+	[erl_syntax:clause(
+	   [erl_syntax:tuple([erl_syntax:underscore(), 
+			      erl_syntax:list([erl_syntax:tuple([erl_syntax:atom(counter), erl_syntax:integer(1)])], 
+					      erl_syntax:underscore())])],
+	   none, [EmptyContentsAst]),
+	 erl_syntax:clause(
+	   [erl_syntax:tuple([erl_syntax:variable("L"), erl_syntax:underscore()])],
+	   none, [erl_syntax:variable("L")])]
+       ),
+      merge_info(merge_info(Info, EmptyContentsInfo), LoopValueInfo)
+     }, TreeWalker2}.
 
 ifchanged_values_ast(Values, {IfContentsAst, IfContentsInfo}, {ElseContentsAst, ElseContentsInfo}, Context, TreeWalker) ->
     Info = merge_info(IfContentsInfo, ElseContentsInfo),
@@ -1170,36 +1260,36 @@ ifchanged_values_ast(Values, {IfContentsAst, IfContentsInfo}, {ElseContentsAst,
                           {ETw, merge_info(LInfo, EInfo), [erl_syntax:tuple([erl_syntax:integer(erlang:phash2(Expr)), EAst])|Acc]} end,
     {TreeWalker1, MergedInfo, Changed} = lists:foldl(ValueAstFun, {TreeWalker, Info,  []}, Values),
     {{erl_syntax:case_expr(erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(ifchanged), [erl_syntax:list(Changed)]),
-        [erl_syntax:clause([erl_syntax:atom(true)], none,
-                [IfContentsAst]),
-            erl_syntax:clause([erl_syntax:underscore()], none,
-                [ElseContentsAst])
-        ]), MergedInfo}, TreeWalker1}.
+			   [erl_syntax:clause([erl_syntax:atom(true)], none,
+					      [IfContentsAst]),
+			    erl_syntax:clause([erl_syntax:underscore()], none,
+					      [ElseContentsAst])
+			   ]), MergedInfo}, TreeWalker1}.
 
 ifchanged_contents_ast(Contents, {IfContentsAst, IfContentsInfo}, {ElseContentsAst, ElseContentsInfo}, _Context, TreeWalker) ->
     Info = merge_info(IfContentsInfo, ElseContentsInfo),
     Key = erl_syntax:integer(erlang:phash2(Contents)),
     {{erl_syntax:case_expr(erl_syntax:application(erl_syntax:atom(erlydtl_runtime), erl_syntax:atom(ifchanged), [erl_syntax:list([erl_syntax:tuple([Key, IfContentsAst])])]),
-        [erl_syntax:clause([erl_syntax:atom(true)], none,
-                [IfContentsAst]),
-            erl_syntax:clause([erl_syntax:underscore()], none,
-                [ElseContentsAst])
-        ]), Info}, TreeWalker}.
+			   [erl_syntax:clause([erl_syntax:atom(true)], none,
+					      [IfContentsAst]),
+			    erl_syntax:clause([erl_syntax:underscore()], none,
+					      [ElseContentsAst])
+			   ]), Info}, TreeWalker}.
 
 
 cycle_ast(Names, Context, TreeWalker) ->
     {NamesTuple, VarNames} = lists:mapfoldl(fun
-            ({string_literal, _, Str}, VarNamesAcc) ->
-                {{S, _}, _} = string_ast(unescape_string_literal(Str), Context, TreeWalker),
-                {S, VarNamesAcc};
-            ({variable, _}=Var, VarNamesAcc) ->
-                {V, VarName} = resolve_variable_ast(Var, Context, true),
-                {V, [VarName|VarNamesAcc]};
-            ({number_literal, _, Num}, VarNamesAcc) ->
-                {format(erl_syntax:integer(Num), Context, TreeWalker), VarNamesAcc};
-            (_, VarNamesAcc) ->
-                {[], VarNamesAcc}
-        end, [], Names),
+						({string_literal, _, Str}, VarNamesAcc) ->
+						   {{S, _}, _} = string_ast(unescape_string_literal(Str), Context, TreeWalker),
+						   {S, VarNamesAcc};
+						({variable, _}=Var, VarNamesAcc) ->
+						   {V, VarName} = resolve_variable_ast(Var, Context, true),
+						   {V, [VarName|VarNamesAcc]};
+						({number_literal, _, Num}, VarNamesAcc) ->
+						   {format(erl_syntax:integer(Num), Context, TreeWalker), VarNamesAcc};
+						(_, VarNamesAcc) ->
+						   {[], VarNamesAcc}
+					   end, [], Names),
     {{erl_syntax:application(
         erl_syntax:atom('erlydtl_runtime'), erl_syntax:atom('cycle'),
         [erl_syntax:tuple(NamesTuple), erl_syntax:variable("Counters")]), #ast_info{ var_names = VarNames }}, TreeWalker}.
@@ -1207,19 +1297,19 @@ cycle_ast(Names, Context, TreeWalker) ->
 %% Older Django templates treat cycle with comma-delimited elements as strings
 cycle_compat_ast(Names, Context, TreeWalker) ->
     NamesTuple = lists:map(fun
-            ({identifier, _, X}) ->
-                    {{S, _}, _} = string_ast(X, Context, TreeWalker),
-                    S
-            end, Names),
+			       ({identifier, _, X}) ->
+				  {{S, _}, _} = string_ast(X, Context, TreeWalker),
+				  S
+			  end, Names),
     {{erl_syntax:application(
         erl_syntax:atom('erlydtl_runtime'), erl_syntax:atom('cycle'),
         [erl_syntax:tuple(NamesTuple), erl_syntax:variable("Counters")]), #ast_info{}}, TreeWalker}.
 
 now_ast(FormatString, Context, TreeWalker) ->
-    % Note: we can't use unescape_string_literal here
-    % because we want to allow escaping in the format string.
-    % We only want to remove the surrounding escapes,
-    % i.e. \"foo\" becomes "foo"
+						% Note: we can't use unescape_string_literal here
+						% because we want to allow escaping in the format string.
+						% We only want to remove the surrounding escapes,
+						% i.e. \"foo\" becomes "foo"
     UnescapeOuter = string:strip(FormatString, both, 34),
     {{StringAst, Info}, TreeWalker1} = string_ast(UnescapeOuter, Context, TreeWalker),
     {{erl_syntax:application(
@@ -1230,9 +1320,9 @@ now_ast(FormatString, Context, TreeWalker) ->
 spaceless_ast(Contents, Context, TreeWalker) ->
     {{Ast, Info}, TreeWalker1} = body_ast(Contents, Context, TreeWalker),
     {{erl_syntax:application(
-                erl_syntax:atom(erlydtl_runtime),
-                erl_syntax:atom(spaceless),
-                [Ast]), Info}, TreeWalker1}.
+	erl_syntax:atom(erlydtl_runtime),
+	erl_syntax:atom(spaceless),
+	[Ast]), Info}, TreeWalker1}.
 
 unescape_string_literal(String) ->
     unescape_string_literal(string:strip(String, both, 34), [], noslash).
@@ -1258,7 +1348,7 @@ full_path(File, DocRoot) ->
         File -> File;
         _ -> filename:join([DocRoot, File])
     end.
-        
+
 %%-------------------------------------------------------------------
 %% Custom tags
 %%-------------------------------------------------------------------
@@ -1270,40 +1360,40 @@ key_to_string(Key) when is_list(Key) ->
 
 tag_ast(Name, Args, Context, TreeWalker) ->
     {{InterpretedArgs, AstInfo1}, TreeWalker1} = lists:foldr(fun
-            ({{identifier, _, Key}, {trans, StringLiteral}}, {{ArgsAcc, AstInfoAcc}, TreeWalkerAcc}) ->
-                {{TransAst, TransAstInfo}, TreeWalker0} = translated_ast(StringLiteral, Context, TreeWalkerAcc),
-                {{[erl_syntax:tuple([erl_syntax:atom(Key), TransAst])|ArgsAcc], merge_info(TransAstInfo, AstInfoAcc)}, TreeWalker0};
-            ({{identifier, _, Key}, Value}, {{ArgsAcc, AstInfoAcc}, TreeWalkerAcc}) ->
-                {{Ast0, AstInfo0}, TreeWalker0} = value_ast(Value, false, false, Context, TreeWalkerAcc),
-                {{[erl_syntax:tuple([erl_syntax:atom(Key), Ast0])|ArgsAcc], merge_info(AstInfo0, AstInfoAcc)}, TreeWalker0}
-        end, {{[], #ast_info{}}, TreeWalker}, Args),
+								 ({{identifier, _, Key}, {trans, StringLiteral}}, {{ArgsAcc, AstInfoAcc}, TreeWalkerAcc}) ->
+								    {{TransAst, TransAstInfo}, TreeWalker0} = translated_ast(StringLiteral, Context, TreeWalkerAcc),
+								    {{[erl_syntax:tuple([erl_syntax:atom(Key), TransAst])|ArgsAcc], merge_info(TransAstInfo, AstInfoAcc)}, TreeWalker0};
+								 ({{identifier, _, Key}, Value}, {{ArgsAcc, AstInfoAcc}, TreeWalkerAcc}) ->
+								    {{Ast0, AstInfo0}, TreeWalker0} = value_ast(Value, false, false, Context, TreeWalkerAcc),
+								    {{[erl_syntax:tuple([erl_syntax:atom(Key), Ast0])|ArgsAcc], merge_info(AstInfo0, AstInfoAcc)}, TreeWalker0}
+							    end, {{[], #ast_info{}}, TreeWalker}, Args),
 
     {RenderAst, RenderInfo} = custom_tags_modules_ast(Name, InterpretedArgs, Context),
     {{RenderAst, merge_info(AstInfo1, RenderInfo)}, TreeWalker1}.
 
 custom_tags_modules_ast(Name, InterpretedArgs, #dtl_context{ custom_tags_modules = [], is_compiling_dir = false }) ->
     {erl_syntax:application(none, erl_syntax:atom(render_tag),
-            [key_to_string(Name), erl_syntax:list(InterpretedArgs),
-             erl_syntax:variable("RenderOptions")]),
-        #ast_info{custom_tags = [Name]}};
+			    [key_to_string(Name), erl_syntax:list(InterpretedArgs),
+			     erl_syntax:variable("RenderOptions")]),
+     #ast_info{custom_tags = [Name]}};
 custom_tags_modules_ast(Name, InterpretedArgs, #dtl_context{ custom_tags_modules = [], is_compiling_dir = true, module = Module }) ->
     {erl_syntax:application(erl_syntax:atom(Module), erl_syntax:atom(Name),
-            [erl_syntax:list(InterpretedArgs), erl_syntax:variable("RenderOptions")]),
-             #ast_info{ custom_tags = [Name] }};
+			    [erl_syntax:list(InterpretedArgs), erl_syntax:variable("RenderOptions")]),
+     #ast_info{ custom_tags = [Name] }};
 custom_tags_modules_ast(Name, InterpretedArgs, #dtl_context{ custom_tags_modules = [Module|Rest] } = Context) ->
     try lists:max([I || {N,I} <- Module:module_info(exports), N =:= Name]) of
         2 ->
             {erl_syntax:application(erl_syntax:atom(Module), erl_syntax:atom(Name),
-                [erl_syntax:list(InterpretedArgs),
-                 erl_syntax:variable("RenderOptions")]), #ast_info{}};
+				    [erl_syntax:list(InterpretedArgs),
+				     erl_syntax:variable("RenderOptions")]), #ast_info{}};
         1 ->
             {erl_syntax:application(erl_syntax:atom(Module), erl_syntax:atom(Name),
-                [erl_syntax:list(InterpretedArgs)]), #ast_info{}};
+				    [erl_syntax:list(InterpretedArgs)]), #ast_info{}};
         I ->
             throw({unsupported_custom_tag_fun, {Module, Name, I}})
     catch _:function_clause ->
-        custom_tags_modules_ast(Name, InterpretedArgs,
-            Context#dtl_context{ custom_tags_modules = Rest })
+	    custom_tags_modules_ast(Name, InterpretedArgs,
+				    Context#dtl_context{ custom_tags_modules = Rest })
     end.
 
 print(true, Fmt, Args) ->
@@ -1317,12 +1407,12 @@ call_ast(Module, TreeWalkerAcc) ->
 call_with_ast(Module, Variable, Context, TreeWalker) ->
     {VarAst, VarName} = resolve_variable_ast(Variable, Context, false),
     call_ast(Module, VarAst, #ast_info{var_names=[VarName]}, TreeWalker).
-        
+
 call_ast(Module, Variable, AstInfo, TreeWalker) ->
-     AppAst = erl_syntax:application(
-		erl_syntax:atom(Module),
-		erl_syntax:atom(render),
-        [Variable, erl_syntax:variable("RenderOptions")]),
+    AppAst = erl_syntax:application(
+	       erl_syntax:atom(Module),
+	       erl_syntax:atom(render),
+	       [Variable, erl_syntax:variable("RenderOptions")]),
     RenderedAst = erl_syntax:variable("Rendered"),
     OkAst = erl_syntax:clause(
 	      [erl_syntax:tuple([erl_syntax:atom(ok), RenderedAst])], 

+ 1 - 1
src/erlydtl_parser.yrl

@@ -1,4 +1,4 @@
-%%%-------------------------------------------------------------------
+%%% -*- mode: erlang -*- ------------------------------------------------------------------
 %%% File:      erlydtl_parser.erl
 %%% @author    Roberto Saccon <rsaccon@gmail.com> [http://rsaccon.com]
 %%% @author    Evan Miller <emmiller@gmail.com>

+ 28 - 18
src/erlydtl_scanner.erl

@@ -2,6 +2,7 @@
 %%% File:      erlydtl_scanner.erl
 %%% @author    Roberto Saccon <rsaccon@gmail.com> [http://rsaccon.com]
 %%% @author    Evan Miller <emmiller@gmail.com>
+%%% @author    Andreas Stenius <kaos@astekk.se>
 %%% @copyright 2008 Roberto Saccon, Evan Miller
 %%% @doc 
 %%% Template language scanner
@@ -34,8 +35,10 @@
 -module(erlydtl_scanner).
 -author('rsaccon@gmail.com').
 -author('emmiller@gmail.com').
+-author('Andreas Stenius <kaos@astekk.se>').
 
--export([scan/1]). 
+-export([scan/1, resume/1]).
+-include("erlydtl_ext.hrl").
 
 
 %%====================================================================
@@ -50,7 +53,11 @@
 %% @end
 %%--------------------------------------------------------------------
 scan(Template) ->
-    scan(Template, [], {1, 1}, in_text).
+    scan(Template, [], {1, 1}, in_text).    
+
+resume(#scanner_state{ template=Template, scanned=Scanned, 
+		     pos=Pos, state=State}) ->
+    scan(Template, Scanned, Pos, State).
 
 scan([], Scanned, _, in_text) ->
     Tokens = lists:reverse(Scanned),
@@ -85,11 +92,11 @@ scan("#}" ++ T, Scanned, {Row, Column}, {in_comment, "#}"}) ->
 
 scan("<!--{%" ++ T, Scanned, {Row, Column}, in_text) ->
     scan(T, [{open_tag, {Row, Column}, '<!--{%'} | Scanned], 
-        {Row, Column + length("<!--{%")}, {in_code, "%}-->"});
+	 {Row, Column + length("<!--{%")}, {in_code, "%}-->"});
 
 scan("{%" ++ T, Scanned, {Row, Column}, in_text) ->
     scan(T, [{open_tag, {Row, Column}, '{%'} | Scanned], 
-        {Row, Column + length("{%")}, {in_code, "%}"});
+	 {Row, Column + length("{%")}, {in_code, "%}"});
 
 scan([_ | T], Scanned, {Row, Column}, {in_comment, Closer}) ->
     scan(T, Scanned, {Row, Column + 1}, {in_comment, Closer});
@@ -124,11 +131,11 @@ scan([$\\ | T], Scanned, {Row, Column}, {in_single_quote, Closer}) ->
 scan([H | T], Scanned, {Row, Column}, {in_single_quote_slash, Closer}) ->
     scan(T, append_char(Scanned, H), {Row, Column + 1}, {in_single_quote, Closer});
 
-% end quote
+						% end quote
 scan("\"" ++ T, Scanned, {Row, Column}, {in_double_quote, Closer}) ->
     scan(T, append_char(Scanned, 34), {Row, Column + 1}, {in_code, Closer});
 
-% treat single quotes the same as double quotes
+						% treat single quotes the same as double quotes
 scan("\'" ++ T, Scanned, {Row, Column}, {in_single_quote, Closer}) ->
     scan(T, append_char(Scanned, 34), {Row, Column + 1}, {in_code, Closer});
 
@@ -141,25 +148,25 @@ scan([H | T], Scanned, {Row, Column}, {in_single_quote, Closer}) ->
 
 scan("}}-->" ++ T, Scanned, {Row, Column}, {_, "}}-->"}) ->
     scan(T, [{close_var, {Row, Column}, '}}-->'} | Scanned], 
-        {Row, Column + length("}}-->")}, in_text);
+	 {Row, Column + length("}}-->")}, in_text);
 
 scan("}}" ++ T, Scanned, {Row, Column}, {_, "}}"}) ->
     scan(T, [{close_var, {Row, Column}, '}}'} | Scanned], {Row, Column + 2}, in_text);
 
 scan("%}-->" ++ T, Scanned, {Row, Column}, {_, "%}-->"}) ->
     scan(T, [{close_tag, {Row, Column}, '%}-->'} | Scanned], 
-        {Row, Column + length("%}-->")}, in_text);
+	 {Row, Column + length("%}-->")}, in_text);
 
 scan("%}" ++ T, [{identifier, _, "mitabrev"}, {open_tag, _, '{%'}|Scanned], {Row, Column}, {_, "%}"}) ->
     scan(T, [{string, {Row, Column + 2}, ""}|Scanned], {Row, Column + 2}, {in_verbatim, undefined});
 
 scan("%}" ++ T, [{identifier, _, ReversedTag}, {identifier, _, "mitabrev"}, {open_tag, _, '{%'}|Scanned], 
-    {Row, Column}, {_, "%}"}) ->
+     {Row, Column}, {_, "%}"}) ->
     scan(T, [{string, {Row, Column + 2}, ""}|Scanned], {Row, Column + 2}, {in_verbatim, ReversedTag});
 
 scan("%}" ++ T, Scanned, {Row, Column}, {_, "%}"}) ->
     scan(T, [{close_tag, {Row, Column}, '%}'} | Scanned], 
-        {Row, Column + 2}, in_text);
+	 {Row, Column + 2}, in_text);
 
 scan("{%" ++ T, Scanned, {Row, Column}, {in_verbatim, Tag}) ->
     scan(T, Scanned, {Row, Column + 2}, {in_verbatim_code, lists:reverse("{%"), Tag});
@@ -172,7 +179,7 @@ scan("endverbatim%}" ++ T, Scanned, {Row, Column}, {in_verbatim_code, _BackTrack
 
 scan("endverbatim " ++ T, Scanned, {Row, Column}, {in_verbatim_code, BackTrack, Tag}) ->
     scan(T, Scanned, {Row, Column + length("endverbatim ")}, 
-        {in_endverbatim_code, "", lists:reverse("endverbatim ", BackTrack), Tag});
+	 {in_endverbatim_code, "", lists:reverse("endverbatim ", BackTrack), Tag});
 
 scan(" " ++ T, Scanned, {Row, Column}, {in_endverbatim_code, "", BackTrack, Tag}) ->
     scan(T, Scanned, {Row, Column + 1}, {in_endverbatim_code, "", [$\ |BackTrack], Tag});
@@ -256,7 +263,8 @@ scan([H | T], Scanned, {Row, Column}, {in_code, Closer}) ->
         digit ->
             scan(T, [{number_literal, {Row, Column}, [H]} | Scanned], {Row, Column + 1}, {in_number, Closer});
         _ ->
-            {error, {Row, ?MODULE, lists:concat(["Illegal character in column ", Column])}}
+            {error, {Row, ?MODULE, lists:concat(["Illegal character in column ", Column])},
+	     #scanner_state{ template=[H|T], scanned=Scanned, pos={Row, Column}, state={in_code, Closer}}}
     end;
 
 scan([H | T], Scanned, {Row, Column}, {in_number, Closer}) ->
@@ -264,7 +272,8 @@ scan([H | T], Scanned, {Row, Column}, {in_number, Closer}) ->
         digit ->
             scan(T, append_char(Scanned, H), {Row, Column + 1}, {in_number, Closer});
         _ ->
-            {error, {Row, ?MODULE, lists:concat(["Illegal character in column ", Column])}}
+            {error, {Row, ?MODULE, lists:concat(["Illegal character in column ", Column])},
+	     #scanner_state{ template=[H|T], scanned=Scanned, pos={Row, Column}, state={in_code, Closer}}}
     end;
 
 scan([H | T], Scanned, {Row, Column}, {in_identifier, Closer}) ->
@@ -274,10 +283,11 @@ scan([H | T], Scanned, {Row, Column}, {in_identifier, Closer}) ->
         digit ->
             scan(T, append_char(Scanned, H), {Row, Column + 1}, {in_identifier, Closer});
         _ ->
-            {error, {Row, ?MODULE, lists:concat(["Illegal character in column ", Column])}}
+            {error, {Row, ?MODULE, lists:concat(["Illegal character in column ", Column])},
+	     #scanner_state{ template=[H|T], scanned=Scanned, pos={Row, Column}, state={in_code, Closer}}}
     end.
 
-% internal functions
+						% internal functions
 
 append_char([{Type, Pos, Chars}|Scanned], Char) ->
     [{Type, Pos, [Char | Chars]} | Scanned].
@@ -328,7 +338,7 @@ mark_keywords([{identifier, Pos, "by" = String}|T], Acc) ->
     mark_keywords(T, [{by_keyword, Pos, String}|Acc]);
 mark_keywords([{identifier, Pos, "with" = String}|T], Acc) ->
     mark_keywords(T, [{with_keyword, Pos, String}|Acc]);
-% These must be succeeded by a close_tag
+						% These must be succeeded by a close_tag
 mark_keywords([{identifier, Pos, "only" = String}, {close_tag, _, _} = CloseTag|T], Acc) ->
     mark_keywords(T, lists:reverse([{only_keyword, Pos, String}, CloseTag], Acc));
 mark_keywords([{identifier, Pos, "parsed" = String}, {close_tag, _, _} = CloseTag|T], Acc) ->
@@ -353,8 +363,8 @@ mark_keywords([{identifier, Pos, "opencomment" = String}, {close_tag, _, _} = Cl
     mark_keywords(T, lists:reverse([{opencomment_keyword, Pos, String}, CloseTag], Acc));
 mark_keywords([{identifier, Pos, "closecomment" = String}, {close_tag, _, _} = CloseTag|T], Acc) ->
     mark_keywords(T, lists:reverse([{closecomment_keyword, Pos, String}, CloseTag], Acc));
-% The rest must be preceded by an open_tag.
-% This allows variables to have the same names as tags.
+						% The rest must be preceded by an open_tag.
+						% This allows variables to have the same names as tags.
 mark_keywords([{open_tag, _, _} = OpenToken, {identifier, Pos, "autoescape" = String}|T], Acc) ->
     mark_keywords(T, lists:reverse([OpenToken, {autoescape_keyword, Pos, String}], Acc));
 mark_keywords([{open_tag, _, _} = OpenToken, {identifier, Pos, "endautoescape" = String}|T], Acc) ->

+ 31 - 0
tests/src/erlydtl_extension_test.erl

@@ -0,0 +1,31 @@
+-module(erlydtl_extension_test).
+
+-export([scan/1, parse/1, compile_ast/3]).
+-include("erlydtl_ext.hrl").
+
+%% look for a foo identifer followed by a #
+scan(#scanner_state{ template="#" ++ T, 
+		     scanned=[{identifier, Loc, "oof"}|Scanned], 
+		     pos={L,C} }=S) ->
+    %% return new state with the hash dropped, and the foo identifer replaced with bar
+    {ok, S#scanner_state{ template=T,
+			  scanned=[{identifier, Loc, "rab"}|Scanned],
+			  pos={L, C+1} }};
+scan(#scanner_state{ template="#" ++ _T, pos={L, C} }) ->
+    %% give error when # not follows foo
+    {error, {L,?MODULE,lists:concat(["Unexpected '#' in code at column ", C])}};
+scan(_) -> 
+    %% for anything else, fallback to the error message from erlydtl_scanner..
+    undefined.
+
+parse(State) ->
+    erlydtl_extension_testparser:resume(State).
+
+%% {{ varA or varB }} is equivalent to {% if varA %}{{ varA }}{% else %}{{ varB }}{% endif %}
+compile_ast({value_or, {Value1, Value2}}, Context, TreeWalker) ->
+    {{V1_Ast, V1_Info}, TW1} = erlydtl_compiler:value_ast(Value1, false, false, Context, TreeWalker),
+    {{V2_Ast, V2_Info}, TW2} = erlydtl_compiler:value_ast(Value2, false, false, Context, TW1),
+    {{erl_syntax:case_expr(V1_Ast,
+                           [erl_syntax:clause([erl_syntax:atom(undefined)], none, [V2_Ast]),
+                            erl_syntax:clause([erl_syntax:underscore()], none, [V1_Ast])
+                           ]), erlydtl_compiler:merge_info(V1_Info, V2_Info)}, TW2}.

+ 153 - 0
tests/src/erlydtl_extension_testparser.yrl

@@ -0,0 +1,153 @@
+%%% -*- mode: erlang -*- ------------------------------------------------------------------
+%%% File:      erlydtl_parser.erl
+%%% @author    Andreas Stenius <kaos@astekk.se>
+%%% @copyright 2013 Andreas Stenius
+%%% @doc Sample extension grammar
+%%% @reference  See <a href="http://erlydtl.googlecode.com" target="_top">http://erlydtl.googlecode.com</a> for more information
+%%% @end  
+%%%
+%%% The MIT License
+%%%
+%%% Copyright (c) 2013 Andreas Stenius
+%%%
+%%% Permission is hereby granted, free of charge, to any person obtaining a copy
+%%% of this software and associated documentation files (the "Software"), to deal
+%%% in the Software without restriction, including without limitation the rights
+%%% to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
+%%% copies of the Software, and to permit persons to whom the Software is
+%%% furnished to do so, subject to the following conditions:
+%%%
+%%% The above copyright notice and this permission notice shall be included in
+%%% all copies or substantial portions of the Software.
+%%%
+%%% THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
+%%% IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
+%%% FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
+%%% AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
+%%% LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
+%%% OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
+%%% THE SOFTWARE.
+%%%
+%%% @since 2013-06-20 by Andreas Stenius
+%%%-------------------------------------------------------------------
+
+Nonterminals
+    Extensions
+    Literal
+
+    ValueExpressionBraced
+
+    ValueExpression
+    Value
+    Variable
+.
+    
+Terminals
+    %% "new" terminals that are partially parsed tokens from the erlydtl parser:
+    variable
+
+    %% standard scanner tokens:
+
+    %% and_keyword
+    %% as_keyword
+    %% autoescape_keyword
+    %% block_keyword
+    %% blocktrans_keyword
+    %% by_keyword
+    %% call_keyword
+    %% close_tag
+    close_var
+    %% comment_keyword
+    %% cycle_keyword
+    %% elif_keyword
+    %% else_keyword
+    %% empty_keyword
+    %% endautoescape_keyword
+    %% endblock_keyword
+    %% endblocktrans_keyword
+    %% endcomment_keyword
+    %% endfilter_keyword
+    %% endfor_keyword
+    %% endif_keyword
+    %% endifchanged_keyword
+    %% endifequal_keyword
+    %% endifnotequal_keyword
+    %% endregroup_keyword
+    %% endspaceless_keyword
+    %% endwith_keyword
+    %% extends_keyword
+    %% filter_keyword
+    %% firstof_keyword
+    %% for_keyword
+    identifier
+    %% if_keyword
+    %% ifchanged_keyword
+    %% ifequal_keyword
+    %% ifnotequal_keyword
+    %% in_keyword
+    %% include_keyword
+    %% noop_keyword
+    %% not_keyword
+    %% now_keyword
+    number_literal
+    %% only_keyword
+    or_keyword
+    %% open_tag
+    open_var
+    %% parsed_keyword
+    %% regroup_keyword
+    %% reversed_keyword
+    %% spaceless_keyword
+    %% ssi_keyword
+    string_literal
+    %% string
+    %% templatetag_keyword
+    %% openblock_keyword
+    %% closeblock_keyword
+    %% openvariable_keyword
+    %% closevariable_keyword
+    %% openbrace_keyword
+    %% closebrace_keyword
+    %% opencomment_keyword
+    %% closecomment_keyword
+    %% trans_keyword
+    %% widthratio_keyword
+    %% with_keyword
+    %% ',' '|' '=' ':' 
+    '.'
+    %% '==' '!='
+    %% '>=' '<='
+    %% '>' '<'
+    %% '(' ')'
+    %% '_'
+.
+
+Rootsymbol
+    Extensions.
+
+%% Operator precedences for the E non terminal
+Left 100 or_keyword.
+%Left 110 and_keyword.
+%Nonassoc 300 '==' '!=' '>=' '<=' '>' '<'.
+%Unary 600 Unot.
+
+Extensions -> ValueExpressionBraced : ['$1'].
+
+ValueExpressionBraced -> open_var ValueExpression close_var : '$2'.
+
+ValueExpression -> Value or_keyword Value : {extension, {value_or, {'$1', '$3'}}}.
+    
+%Value -> Value '|' Filter : {apply_filter, '$1', '$3'}.
+%Value -> '_' '(' Value ')' : {trans, '$3'}.
+Value -> Variable : '$1'.
+Value -> Literal : '$1'.
+    
+Variable -> identifier : {variable, '$1'}.
+Variable -> variable : '$1'.
+Variable -> Variable '.' identifier : {attribute, {'$3', '$1'}}.
+
+Literal -> string_literal : '$1'.
+Literal -> number_literal : '$1'.
+
+
+%% vim: syntax=erlang

+ 1136 - 1126
tests/src/erlydtl_unittests.erl

@@ -1,1180 +1,1190 @@
 -module(erlydtl_unittests).
- 
+
 -export([run_tests/0]).
- 
+
 tests() ->
     [
-        {"vars", [
-                {"string",
-                    <<"String value is: {{ var1 }}">>,
-                    [{var1, "foo"}], <<"String value is: foo">>},
-                {"int",
-                    <<"The magic number is: {{ var1 }}">>,
-                    [{var1, 42}], <<"The magic number is: 42">>},
-                {"float",
-                    <<"The price of milk is: {{ var1 }}">>,
-                    [{var1, 0.42}], <<"The price of milk is: 0.42">>},
-                {"No spaces",
-                    <<"{{var1}}">>,
-                    [{var1, "foo"}], <<"foo">>},
-                {"Variable name is a tag name",
-                    <<"{{ comment }}">>,
-                    [{comment, "Nice work!"}], <<"Nice work!">>}
-            ]},
-        {"comment", [
-                {"comment block is excised",
-                    <<"bob {% comment %}(moron){% endcomment %} loblaw">>,
-                    [], <<"bob  loblaw">>},
-                {"inline comment is excised",
-                    <<"you're {# not #} a very nice person">>,
-                    [], <<"you're  a very nice person">>}
-            ]},
-        {"autoescape", [
-                {"Autoescape works",
-                    <<"{% autoescape on %}{{ var1 }}{% endautoescape %}">>,
-                    [{var1, "<b>bold</b>"}], <<"&lt;b&gt;bold&lt;/b&gt;">>},
-                {"Nested autoescape",
-                    <<"{% autoescape on %}{{ var1 }}{% autoescape off %}{{ var1 }}{% endautoescape %}{% endautoescape %}">>,
-                    [{var1, "<b>"}], <<"&lt;b&gt;<b>">>}
-            ]},
-        {"string literal", [
-                {"Render literal",
-                    <<"{{ \"foo\" }} is my name">>, [], <<"foo is my name">>},
-                {"Newlines are escaped",
-                    <<"{{ \"foo\\n\" }}">>, [], <<"foo\n">>}
-            ]},
-        {"cycle", [
+     {"vars", [
+	       {"string",
+		<<"String value is: {{ var1 }}">>,
+		[{var1, "foo"}], <<"String value is: foo">>},
+	       {"int",
+		<<"The magic number is: {{ var1 }}">>,
+		[{var1, 42}], <<"The magic number is: 42">>},
+	       {"float",
+		<<"The price of milk is: {{ var1 }}">>,
+		[{var1, 0.42}], <<"The price of milk is: 0.42">>},
+	       {"No spaces",
+		<<"{{var1}}">>,
+		[{var1, "foo"}], <<"foo">>},
+	       {"Variable name is a tag name",
+		<<"{{ comment }}">>,
+		[{comment, "Nice work!"}], <<"Nice work!">>}
+	      ]},
+     {"comment", [
+		  {"comment block is excised",
+		   <<"bob {% comment %}(moron){% endcomment %} loblaw">>,
+		   [], <<"bob  loblaw">>},
+		  {"inline comment is excised",
+		   <<"you're {# not #} a very nice person">>,
+		   [], <<"you're  a very nice person">>}
+		 ]},
+     {"autoescape", [
+		     {"Autoescape works",
+		      <<"{% autoescape on %}{{ var1 }}{% endautoescape %}">>,
+		      [{var1, "<b>bold</b>"}], <<"&lt;b&gt;bold&lt;/b&gt;">>},
+		     {"Nested autoescape",
+		      <<"{% autoescape on %}{{ var1 }}{% autoescape off %}{{ var1 }}{% endautoescape %}{% endautoescape %}">>,
+		      [{var1, "<b>"}], <<"&lt;b&gt;<b>">>}
+		    ]},
+     {"string literal", [
+			 {"Render literal",
+			  <<"{{ \"foo\" }} is my name">>, [], <<"foo is my name">>},
+			 {"Newlines are escaped",
+			  <<"{{ \"foo\\n\" }}">>, [], <<"foo\n">>}
+			]},
+     {"cycle", [
                 {"Cycling through quoted strings",
-                    <<"{% for i in test %}{% cycle 'a' 'b' %}{{ i }},{% endfor %}">>,
-                    [{test, ["0", "1", "2", "3", "4"]}], <<"a0,b1,a2,b3,a4,">>},
+		 <<"{% for i in test %}{% cycle 'a' 'b' %}{{ i }},{% endfor %}">>,
+		 [{test, ["0", "1", "2", "3", "4"]}], <<"a0,b1,a2,b3,a4,">>},
                 {"Cycling through normal variables",
-                    <<"{% for i in test %}{% cycle aye bee %}{{ i }},{% endfor %}">>,
-                    [{test, ["0", "1", "2", "3", "4"]}, {aye, "a"}, {bee, "b"}],
-                    <<"a0,b1,a2,b3,a4,">>}
-            ]},
-        {"number literal", [
-                {"Render integer",
-                    <<"{{ 5 }}">>, [], <<"5">>}
-            ]},
-        {"variable", [
-                {"Render variable",
+		 <<"{% for i in test %}{% cycle aye bee %}{{ i }},{% endfor %}">>,
+		 [{test, ["0", "1", "2", "3", "4"]}, {aye, "a"}, {bee, "b"}],
+		 <<"a0,b1,a2,b3,a4,">>}
+	       ]},
+     {"number literal", [
+			 {"Render integer",
+			  <<"{{ 5 }}">>, [], <<"5">>}
+			]},
+     {"variable", [
+		   {"Render variable",
                     <<"{{ var1 }} is my game">>, [{var1, "bar"}], <<"bar is my game">>},
-                {"Render variable with attribute",
+		   {"Render variable with attribute",
                     <<"I enjoy {{ var1.game }}">>, [{var1, [{game, "Othello"}]}], <<"I enjoy Othello">>},
-                {"Render variable with string-key attribute",
+		   {"Render variable with string-key attribute",
                     <<"I also enjoy {{ var1.game }}">>, [{var1, [{"game", "Parcheesi"}]}], <<"I also enjoy Parcheesi">>},
-                {"Render variable with binary-key attribute",
+		   {"Render variable with binary-key attribute",
                     <<"I also enjoy {{ var1.game }}">>, [{var1, [{<<"game">>, "Parcheesi"}]}], <<"I also enjoy Parcheesi">>},
-                {"Render variable in dict",
+		   {"Render variable in dict",
                     <<"{{ var1 }}">>, dict:store(var1, "bar", dict:new()), <<"bar">>},
-                {"Render variable in gb_tree",
+		   {"Render variable in gb_tree",
                     <<"{{ var1 }}">>, gb_trees:insert(var1, "bar", gb_trees:empty()), <<"bar">>},
-                {"Render variable in arity-1 func",
+		   {"Render variable in arity-1 func",
                     <<"I enjoy {{ var1 }}">>, fun (var1) -> "Othello" end, <<"I enjoy Othello">>},
-                {"Render variable with attribute in dict",
+		   {"Render variable with attribute in dict",
                     <<"{{ var1.attr }}">>, [{var1, dict:store(attr, "Othello", dict:new())}], <<"Othello">>},
-                {"Render variable with attribute in gb_tree",
+		   {"Render variable with attribute in gb_tree",
                     <<"{{ var1.attr }}">>, [{var1, gb_trees:insert(attr, "Othello", gb_trees:empty())}], <<"Othello">>},
-                {"Render variable with attribute in arity-1 func",
+		   {"Render variable with attribute in arity-1 func",
                     <<"I enjoy {{ var1.game }}">>, [{var1, fun (game) -> "Othello" end}], <<"I enjoy Othello">>},
-                {"Render variable in parameterized module",
+		   {"Render variable in parameterized module",
                     <<"{{ var1.some_var }}">>, [{var1, erlydtl_example_variable_storage:new("foo")}], <<"foo">>},
-                {"Nested attributes",
+		   {"Nested attributes",
                     <<"{{ person.city.state.country }}">>, [{person, [{city, [{state, [{country, "Italy"}]}]}]}],
                     <<"Italy">>}
+		  ]},
+     {"now", [
+	      {"now functional",
+	       <<"It is the {% now \"jS o\\f F Y\" %}.">>, [{var1, ""}], generate_test_date()}
+	     ]},
+     {"if", [
+	     {"If/else",
+	      <<"{% if var1 %}boo{% else %}yay{% endif %}">>, [{var1, ""}], <<"yay">>},
+	     {"If elif",
+	      <<"{% if var1 %}boo{% elif var2 %}yay{% endif %}">>, [{var1, ""}, {var2, "happy"}], <<"yay">>},
+	     {"If elif/else",
+	      <<"{% if var1 %}boo{% elif var2 %}sad{% else %}yay{% endif %}">>, [{var1, ""}, {var2, ""}], <<"yay">>},
+	     {"If elif/elif/else",
+	      <<"{% if var1 %}boo{% elif var2 %}yay{% elif var3 %}sad{% else %}noo{% endif %}">>, [{var1, ""},
+												   {var2, "happy"}, {var3, "not_taken"}], <<"yay">>},
+	     {"If",
+	      <<"{% if var1 %}boo{% endif %}">>, [{var1, ""}], <<>>},
+	     {"If not",
+	      <<"{% if not var1 %}yay{% endif %}">>, [{var1, ""}], <<"yay">>},
+	     {"If \"0\"",
+	      <<"{% if var1 %}boo{% endif %}">>, [{var1, "0"}], <<>>},
+	     {"If false",
+	      <<"{% if var1 %}boo{% endif %}">>, [{var1, false}], <<>>},
+	     {"If false string",
+	      <<"{% if var1 %}boo{% endif %}">>, [{var1, "false"}], <<"boo">>},
+	     {"If undefined",
+	      <<"{% if var1 %}boo{% endif %}">>, [{var1, undefined}], <<>>},
+	     {"If other atom",
+	      <<"{% if var1 %}yay{% endif %}">>, [{var1, foobar}], <<"yay">>},
+	     {"If non-empty string",
+	      <<"{% if var1 %}yay{% endif %}">>, [{var1, "hello"}], <<"yay">>},
+	     {"If proplist",
+	      <<"{% if var1 %}yay{% endif %}">>, [{var1, [{foo, "bar"}]}], <<"yay">>},
+	     {"If complex",
+	      <<"{% if foo.bar.baz %}omgwtfbbq{% endif %}">>, [], <<"">>}
             ]},
-        {"now", [
-               {"now functional",
-                  <<"It is the {% now \"jS o\\f F Y\" %}.">>, [{var1, ""}], generate_test_date()}
-            ]},
-        {"if", [
-                {"If/else",
-                    <<"{% if var1 %}boo{% else %}yay{% endif %}">>, [{var1, ""}], <<"yay">>},
-                {"If elif",
-		    <<"{% if var1 %}boo{% elif var2 %}yay{% endif %}">>, [{var1, ""}, {var2, "happy"}], <<"yay">>},
-                {"If elif/else",
-		    <<"{% if var1 %}boo{% elif var2 %}sad{% else %}yay{% endif %}">>, [{var1, ""}, {var2, ""}], <<"yay">>},
-                {"If elif/elif/else",
-		    <<"{% if var1 %}boo{% elif var2 %}yay{% elif var3 %}sad{% else %}noo{% endif %}">>, [{var1, ""},
-			{var2, "happy"}, {var3, "not_taken"}], <<"yay">>},
-                {"If",
-                    <<"{% if var1 %}boo{% endif %}">>, [{var1, ""}], <<>>},
-                {"If not",
-                    <<"{% if not var1 %}yay{% endif %}">>, [{var1, ""}], <<"yay">>},
-                {"If \"0\"",
-                    <<"{% if var1 %}boo{% endif %}">>, [{var1, "0"}], <<>>},
-                {"If false",
-                    <<"{% if var1 %}boo{% endif %}">>, [{var1, false}], <<>>},
-                {"If false string",
-                    <<"{% if var1 %}boo{% endif %}">>, [{var1, "false"}], <<"boo">>},
-                {"If undefined",
-                    <<"{% if var1 %}boo{% endif %}">>, [{var1, undefined}], <<>>},
-                {"If other atom",
-                    <<"{% if var1 %}yay{% endif %}">>, [{var1, foobar}], <<"yay">>},
-                {"If non-empty string",
-                    <<"{% if var1 %}yay{% endif %}">>, [{var1, "hello"}], <<"yay">>},
-                {"If proplist",
-                    <<"{% if var1 %}yay{% endif %}">>, [{var1, [{foo, "bar"}]}], <<"yay">>},
-                {"If complex",
-                    <<"{% if foo.bar.baz %}omgwtfbbq{% endif %}">>, [], <<"">>}
-            ]},
-        {"if .. in ..", [
-                {"If substring in string",
-                    <<"{% if var1 in var2 %}yay{% endif %}">>, [{var1, "rook"}, {var2, "Crooks"}], <<"yay">>},
-                {"If substring in string (false)",
-                    <<"{% if var1 in var2 %}boo{% endif %}">>, [{var1, "Cook"}, {var2, "Crooks"}], <<>>},
-                {"If substring not in string",
-                    <<"{% if var1 not in var2 %}yay{% endif %}">>, [{var1, "Cook"}, {var2, "Crooks"}], <<"yay">>},
-                {"If substring not in string (false)",
-                    <<"{% if var1 not in var2 %}boo{% endif %}">>, [{var1, "rook"}, {var2, "Crooks"}], <<>>},
-                {"If literal substring in string",
-                    <<"{% if \"man\" in \"Ottoman\" %}yay{% endif %}">>, [], <<"yay">>},
-                {"If literal substring in string (false)",
-                    <<"{% if \"woman\" in \"Ottoman\" %}boo{% endif %}">>, [], <<>>},
-                {"If element in list",
-                    <<"{% if var1 in var2 %}yay{% endif %}">>, [{var1, "foo"}, {var2, ["bar", "foo", "baz"]}], <<"yay">>},
-                {"If element in list (false)",
-                    <<"{% if var1 in var2 %}boo{% endif %}">>, [{var1, "FOO"}, {var2, ["bar", "foo", "baz"]}], <<>>}
-            ]},
-        {"if .. and ..", [
-                {"If true and true",
-                    <<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, true}, {var2, true}], <<"yay">>},
-                {"If true and false",
-                    <<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, true}, {var2, false}], <<"">>},
-                {"If false and true",
-                    <<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, false}, {var2, true}], <<"">>},
-                {"If false and false ",
-                    <<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, false}, {var2, false}], <<"">>}
-            ]},
-        {"if .. or ..", [
-                {"If true or true",
-                    <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, true}, {var2, true}], <<"yay">>},
-                {"If true or false",
-                    <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, true}, {var2, false}], <<"yay">>},
-                {"If false or true",
-                    <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, false}, {var2, true}], <<"yay">>},
-                {"If false or false ",
-                    <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, false}, {var2, false}], <<"">>}
-            ]},
-        {"if equality", [
-                {"If int equals number literal",
-                    <<"{% if var1 == 2 %}yay{% endif %}">>, [{var1, 2}], <<"yay">>},
-                {"If int equals number literal (false)",
-                    <<"{% if var1 == 2 %}yay{% endif %}">>, [{var1, 3}], <<"">>},
-                {"If string equals string literal",
-                    <<"{% if var1 == \"2\" %}yay{% endif %}">>, [{var1, "2"}], <<"yay">>},
-                {"If string equals string literal (false)",
-                    <<"{% if var1 == \"2\" %}yay{% endif %}">>, [{var1, "3"}], <<"">>},
-                {"If int not equals number literal",
-                    <<"{% if var1 != 2 %}yay{% endif %}">>, [{var1, 3}], <<"yay">>},
-                {"If string not equals string literal",
-                    <<"{% if var1 != \"2\" %}yay{% endif %}">>, [{var1, "3"}], <<"yay">>},
-                {"If filter result equals number literal",
-                    <<"{% if var1|length == 2 %}yay{% endif %}">>, [{var1, ["fo", "bo"]}], <<"yay">>},
-                {"If filter result equals string literal",
-                    <<"{% if var1|capfirst == \"Foo\" %}yay{% endif %}">>, [{var1, "foo"}], <<"yay">>}
-            ]},
-        {"if size comparison", [
-                {"If int greater than number literal",
-                    <<"{% if var1 > 2 %}yay{% endif %}">>, [{var1, 3}], <<"yay">>},
-                {"If int greater than negative number literal",
-                    <<"{% if var1 > -2 %}yay{% endif %}">>, [{var1, -1}], <<"yay">>},
-                {"If int greater than number literal (false)",
-                    <<"{% if var1 > 2 %}yay{% endif %}">>, [{var1, 2}], <<"">>},
- 
-                {"If int greater than or equal to number literal",
-                    <<"{% if var1 >= 2 %}yay{% endif %}">>, [{var1, 3}], <<"yay">>},
-                {"If int greater than or equal to number literal (2)",
-                    <<"{% if var1 >= 2 %}yay{% endif %}">>, [{var1, 2}], <<"yay">>},
-                {"If int greater than or equal to number literal (false)",
-                    <<"{% if var1 >= 2 %}yay{% endif %}">>, [{var1, 1}], <<"">>},
- 
-                {"If int less than number literal",
-                    <<"{% if var1 < 2 %}yay{% endif %}">>, [{var1, 1}], <<"yay">>},
-                {"If int less than number literal (false)",
-                    <<"{% if var1 < 2 %}yay{% endif %}">>, [{var1, 2}], <<"">>},
- 
-                {"If int less than or equal to number literal",
-                    <<"{% if var1 <= 2 %}yay{% endif %}">>, [{var1, 1}], <<"yay">>},
-                {"If int less than or equal to number literal",
-                    <<"{% if var1 <= 2 %}yay{% endif %}">>, [{var1, 2}], <<"yay">>},
-                {"If int less than or equal to number literal (false)",
-                    <<"{% if var1 <= 2 %}yay{% endif %}">>, [{var1, 3}], <<"">>}
-            ]},
-        {"if complex bool", [
-                {"If (true or false) and true",
-                    <<"{% if (var1 or var2) and var3 %}yay{% endif %}">>,
-                    [{var1, true}, {var2, false}, {var3, true}], <<"yay">>},
-                {"If true or (false and true)",
-                    <<"{% if var1 or (var2 and var3) %}yay{% endif %}">>,
-                    [{var1, true}, {var2, false}, {var3, true}], <<"yay">>}
-            ]},
-        {"for", [
-                {"Simple loop",
-                    <<"{% for x in list %}{{ x }}{% endfor %}">>, [{'list', ["1", "2", "3"]}],
-                    <<"123">>},
-                {"Reversed loop",
-                    <<"{% for x in list reversed %}{{ x }}{% endfor %}">>, [{'list', ["1", "2", "3"]}],
-                    <<"321">>},
-                {"Expand list",
-                    <<"{% for x, y in list %}{{ x }},{{ y }}\n{% endfor %}">>, [{'list', [["X", "1"], ["X", "2"]]}],
-                    <<"X,1\nX,2\n">>},
-                {"Expand tuple",
-                    <<"{% for x, y in list %}{{ x }},{{ y }}\n{% endfor %}">>, [{'list', [{"X", "1"}, {"X", "2"}]}],
-                    <<"X,1\nX,2\n">>},
-                {"Resolve variable attribute",
-                    <<"{% for number in person.numbers %}{{ number }}\n{% endfor %}">>, [{person, [{numbers, ["411", "911"]}]}],
-                    <<"411\n911\n">>},
-                {"Resolve nested variable attribute",
-                    <<"{% for number in person.home.numbers %}{{ number }}\n{% endfor %}">>, [{person, [{home, [{numbers, ["411", "911"]}]}]}],
-                    <<"411\n911\n">>},
-                {"Counter0",
-                    <<"{% for number in numbers %}{{ forloop.counter0 }}. {{ number }}\n{% endfor %}">>,
-                    [{numbers, ["Zero", "One", "Two"]}], <<"0. Zero\n1. One\n2. Two\n">>},
-                {"Counter",
-                    <<"{% for number in numbers %}{{ forloop.counter }}. {{ number }}\n{% endfor %}">>,
-                    [{numbers, ["One", "Two", "Three"]}], <<"1. One\n2. Two\n3. Three\n">>},
-                {"Reverse Counter0",
-                    <<"{% for number in numbers %}{{ forloop.revcounter0 }}. {{ number }}\n{% endfor %}">>,
-                    [{numbers, ["Two", "One", "Zero"]}], <<"2. Two\n1. One\n0. Zero\n">>},
-                {"Reverse Counter",
-                    <<"{% for number in numbers %}{{ forloop.revcounter }}. {{ number }}\n{% endfor %}">>,
-                    [{numbers, ["Three", "Two", "One"]}], <<"3. Three\n2. Two\n1. One\n">>},
-                {"Counter \"first\"",
-                    <<"{% for number in numbers %}{% if forloop.first %}{{ number }}{% endif %}{% endfor %}">>,
-                    [{numbers, ["One", "Two", "Three"]}], <<"One">>},
-                {"Counter \"last\"",
-                    <<"{% for number in numbers %}{% if forloop.last %}{{ number }}{% endif %}{% endfor %}">>,
-                    [{numbers, ["One", "Two", "Three"]}], <<"Three">>},
-                {"Nested for loop",
-                    <<"{% for outer in list %}{% for inner in outer %}{{ inner }}\n{% endfor %}{% endfor %}">>,
-                    [{'list', [["Al", "Albert"], ["Jo", "Joseph"]]}],
-                    <<"Al\nAlbert\nJo\nJoseph\n">>},
-                {"Access parent loop counters",
-                    <<"{% for outer in list %}{% for inner in outer %}({{ forloop.parentloop.counter0 }}, {{ forloop.counter0 }})\n{% endfor %}{% endfor %}">>,
-                    [{'list', [["One", "two"], ["One", "two"]]}], <<"(0, 0)\n(0, 1)\n(1, 0)\n(1, 1)\n">>},
-                {"If changed",
-                    <<"{% for x in list %}{% ifchanged %}{{ x }}\n{% endifchanged %}{% endfor %}">>,
-                    [{'list', ["one", "two", "two", "three", "three", "three"]}], <<"one\ntwo\nthree\n">>},
-                {"If changed/2",
-                    <<"{% for x, y in list %}{% ifchanged %}{{ x|upper }}{% endifchanged %}{% ifchanged %}{{ y|lower }}{% endifchanged %}\n{% endfor %}">>,
-                    [{'list', [["one", "a"], ["two", "A"], ["two", "B"], ["three", "b"], ["three", "c"], ["Three", "b"]]}], <<"ONEa\nTWO\nb\nTHREE\nc\nb\n">>},
-                {"If changed/else",
-                    <<"{% for x in list %}{% ifchanged %}{{ x }}\n{% else %}foo\n{% endifchanged %}{% endfor %}">>,
-                    [{'list', ["one", "two", "two", "three", "three", "three"]}], <<"one\ntwo\nfoo\nthree\nfoo\nfoo\n">>},
-                {"If changed/param",
-                    <<"{% for date in list %}{% ifchanged date.month %} {{ date.month }}:{{ date.day }}{% else %},{{ date.day }}{% endifchanged %}{% endfor %}\n">>,
-                    [{'list', [[{month,"Jan"},{day,1}],[{month,"Jan"},{day,2}],[{month,"Apr"},{day,10}],
-                               [{month,"Apr"},{day,11}],[{month,"May"},{day,4}]]}], 
-                    <<" Jan:1,2 Apr:10,11 May:4\n">>},
-                {"If changed/param2",
-                    <<"{% for x, y in list %}{% ifchanged y|upper %}{{ x|upper }}{% endifchanged %}\n{% endfor %}">>,
-                    [{'list', [["one", "a"], ["two", "A"], ["two", "B"], ["three", "b"], ["three", "c"], ["Three", "b"]]}], <<"ONE\n\nTWO\n\nTHREE\nTHREE\n">>},
-                {"If changed/param2 combined",
-                    <<"{% for x, y in list %}{% ifchanged x y|upper %}{{ x }}{% endifchanged %}\n{% endfor %}">>,
-                    [{'list', [["one", "a"], ["two", "A"], ["two", "B"], ["three", "b"], ["three", "B"], ["three", "c"]]}], <<"one\ntwo\ntwo\nthree\n\nthree\n">>},
-                {"If changed/resolve",
-                    <<"{% for x in list %}{% ifchanged x.name|first %}{{ x.value }}{% endifchanged %}\n{% endfor %}">>,
-                    [{'list', [[{"name", ["nA","nB"]},{"value","1"}],[{"name", ["nA","nC"]},{"value","2"}],
-                               [{"name", ["nB","nC"]},{"value","3"}],[{"name", ["nB","nA"]},{"value","4"}]]}],
-                    <<"1\n\n3\n\n">>}
-            ]},
-        {"for/empty", [
-                {"Simple loop",
-                    <<"{% for x in list %}{{ x }}{% empty %}shucks{% endfor %}">>, [{'list', ["1", "2", "3"]}],
-                    <<"123">>},
-                {"Simple loop (empty)",
-                    <<"{% for x in list %}{{ x }}{% empty %}shucks{% endfor %}">>, [{'list', []}],
-                    <<"shucks">>}
-            ]},
-        {"ifequal", [
-                {"Compare variable to literal",
-                    <<"{% ifequal var1 \"foo\" %}yay{% endifequal %}">>,
-                    [{var1, "foo"}], <<"yay">>},
-                {"Compare variable to unequal literal",
-                    <<"{% ifequal var1 \"foo\" %}boo{% endifequal %}">>,
-                    [{var1, "bar"}], <<>>},
-                {"Compare literal to variable",
-                    <<"{% ifequal \"foo\" var1 %}yay{% endifequal %}">>,
-                    [{var1, "foo"}], <<"yay">>},
-                {"Compare literal to unequal variable",
-                    <<"{% ifequal \"foo\" var1 %}boo{% endifequal %}">>,
-                    [{var1, "bar"}], <<>>},
-                {"Compare variable to literal (int string)",
-                    <<"{% ifequal var1 \"2\" %}yay{% else %}boo{% endifequal %}">>,
-                    [{var1, "2"}], <<"yay">>},
-                {"Compare variable to literal (int)",
-                    <<"{% ifequal var1 2 %}yay{% else %}boo{% endifequal %}">>,
-                    [{var1, 2}], <<"yay">>},
-                {"Compare variable to unequal literal (int)",
-                    <<"{% ifequal var1 2 %}boo{% else %}yay{% endifequal %}">>,
-                    [{var1, 3}], <<"yay">>},
-                {"Compare variable to equal literal (atom)",
-                    <<"{% ifequal var1 \"foo\"%}yay{% endifequal %}">>,
-                    [{var1, foo}], <<"yay">>},
-                {"Compare variable to unequal literal (atom)",
-                    <<"{% ifequal var1 \"foo\"%}yay{% else %}boo{% endifequal %}">>,
-                    [{var1, bar}], <<"boo">>}
-            ]},
-        {"ifequal/else", [
-                {"Compare variable to literal",
-                    <<"{% ifequal var1 \"foo\" %}yay{% else %}boo{% endifequal %}">>,
-                    [{var1, "foo"}], <<"yay">>},
-                {"Compare variable to unequal literal",
-                    <<"{% ifequal var1 \"foo\" %}boo{% else %}yay{% endifequal %}">>,
-                    [{var1, "bar"}], <<"yay">>},
-                {"Compare literal to variable",
-                    <<"{% ifequal \"foo\" var1 %}yay{% else %}boo{% endifequal %}">>,
-                    [{var1, "foo"}], <<"yay">>},
-                {"Compare literal to unequal variable",
-                    <<"{% ifequal \"foo\" var1 %}boo{% else %}yay{% endifequal %}">>,
-                    [{var1, "bar"}], <<"yay">>}
-            ]},
-        {"ifnotequal", [
-                {"Compare variable to literal",
-                    <<"{% ifnotequal var1 \"foo\" %}boo{% endifnotequal %}">>,
-                    [{var1, "foo"}], <<>>},
-                {"Compare variable to unequal literal",
-                    <<"{% ifnotequal var1 \"foo\" %}yay{% endifnotequal %}">>,
-                    [{var1, "bar"}], <<"yay">>},
-                {"Compare literal to variable",
-                    <<"{% ifnotequal \"foo\" var1 %}boo{% endifnotequal %}">>,
-                    [{var1, "foo"}], <<>>},
-                {"Compare literal to unequal variable",
-                    <<"{% ifnotequal \"foo\" var1 %}yay{% endifnotequal %}">>,
-                    [{var1, "bar"}], <<"yay">>}
-            ]},
-        {"ifnotequal/else", [
-                {"Compare variable to literal",
-                    <<"{% ifnotequal var1 \"foo\" %}boo{% else %}yay{% endifnotequal %}">>,
-                    [{var1, "foo"}], <<"yay">>},
-                {"Compare variable to unequal literal",
-                    <<"{% ifnotequal var1 \"foo\" %}yay{% else %}boo{% endifnotequal %}">>,
-                    [{var1, "bar"}], <<"yay">>},
-                {"Compare literal to variable",
-                    <<"{% ifnotequal \"foo\" var1 %}boo{% else %}yay{% endifnotequal %}">>,
-                    [{var1, "foo"}], <<"yay">>},
-                {"Compare literal to unequal variable",
-                    <<"{% ifnotequal \"foo\" var1 %}yay{% else %}boo{% endifnotequal %}">>,
-                    [{var1, "bar"}], <<"yay">>}
-            ]},
-        {"filter tag", [
-                {"Apply a filter",
-                    <<"{% filter escape %}&{% endfilter %}">>, [], <<"&amp;">>},
-                {"Chained filters",
-                    <<"{% filter linebreaksbr|escape %}\n{% endfilter %}">>, [], <<"&lt;br /&gt;">>}
-            ]},
-        {"filters", [
-               {"Filter a literal",
-                    <<"{{ \"pop\"|capfirst }}">>, [],
-                    <<"Pop">>},
-                {"Filters applied in order",
-                    <<"{{ var1|force_escape|length }}">>, [{var1, <<"&">>}],
-                    <<"5">>},
-                {"Escape is applied last",
-                    <<"{{ var1|escape|linebreaksbr }}">>, [{var1, <<"\n">>}],
-                    <<"&lt;br /&gt;">>},
-		{"add; lhs number, rhs number",
-		      <<"{{ one|add:4}}">>, [{one, 1}],
-		      <<"5">>},
-		{"add; lhs numeric string, rhs number",
-		      <<"{{ one|add:4}}">>, [{one, "1"}],
-		      <<"5">>},
-		{"add; lhs number, rhs numeric string",
-		      <<"{{ one|add:'4'}}">>, [{one, 1}],
-		      <<"5">>},
-		{"add; lhs non-numeric string, rhs number",
-		      <<"{{ one|add:4}}">>, [{one, "foo"}],
-		      <<"foo4">>},
-		{"add; lhs number, rhs non-numeric string",
-		      <<"{{ one|add:'foo'}}">>, [{one, 1}],
-		      <<"1foo">>},
-		{"add; lhs non-numeric string, rhs non-numeric string",
-		      <<"{{ one|add:'bar'}}">>, [{one, "foo"}],
-		      <<"foobar">>},
-		{"add; lhs numeric string, rhs numeric string",
-		      <<"{{ one|add:'4'}}">>, [{one, "1"}],
-		      <<"5">>},
-                {"|addslashes",
-                    <<"{{ var1|addslashes }}">>, [{var1, "Jimmy's \"great\" meats'n'things"}],
-                    <<"Jimmy\\'s \\\"great\\\" meats\\'n\\'things">>},
-                {"|capfirst",
-                    <<"{{ var1|capfirst }}">>, [{var1, "dana boyd"}],
-                    <<"Dana boyd">>},
-                {"|center:10",
-                    <<"{{ var1|center:10 }}">>, [{var1, "MB"}],
-                    <<"    MB    ">>},
-                {"|center:1",
-                    <<"{{ var1|center:1 }}">>, [{var1, "KBR"}],
-                    <<"B">>},
-                {"|cut:\" \"",
-                    <<"{{ var1|cut:\" \" }}">>, [{var1, "String with spaces"}],
-                    <<"Stringwithspaces">>},
-                {"|date 1",
+     {"if .. in ..", [
+		      {"If substring in string",
+		       <<"{% if var1 in var2 %}yay{% endif %}">>, [{var1, "rook"}, {var2, "Crooks"}], <<"yay">>},
+		      {"If substring in string (false)",
+		       <<"{% if var1 in var2 %}boo{% endif %}">>, [{var1, "Cook"}, {var2, "Crooks"}], <<>>},
+		      {"If substring not in string",
+		       <<"{% if var1 not in var2 %}yay{% endif %}">>, [{var1, "Cook"}, {var2, "Crooks"}], <<"yay">>},
+		      {"If substring not in string (false)",
+		       <<"{% if var1 not in var2 %}boo{% endif %}">>, [{var1, "rook"}, {var2, "Crooks"}], <<>>},
+		      {"If literal substring in string",
+		       <<"{% if \"man\" in \"Ottoman\" %}yay{% endif %}">>, [], <<"yay">>},
+		      {"If literal substring in string (false)",
+		       <<"{% if \"woman\" in \"Ottoman\" %}boo{% endif %}">>, [], <<>>},
+		      {"If element in list",
+		       <<"{% if var1 in var2 %}yay{% endif %}">>, [{var1, "foo"}, {var2, ["bar", "foo", "baz"]}], <<"yay">>},
+		      {"If element in list (false)",
+		       <<"{% if var1 in var2 %}boo{% endif %}">>, [{var1, "FOO"}, {var2, ["bar", "foo", "baz"]}], <<>>}
+		     ]},
+     {"if .. and ..", [
+		       {"If true and true",
+			<<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, true}, {var2, true}], <<"yay">>},
+		       {"If true and false",
+			<<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, true}, {var2, false}], <<"">>},
+		       {"If false and true",
+			<<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, false}, {var2, true}], <<"">>},
+		       {"If false and false ",
+			<<"{% if var1 and var2 %}yay{% endif %}">>, [{var1, false}, {var2, false}], <<"">>}
+		      ]},
+     {"if .. or ..", [
+		      {"If true or true",
+		       <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, true}, {var2, true}], <<"yay">>},
+		      {"If true or false",
+		       <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, true}, {var2, false}], <<"yay">>},
+		      {"If false or true",
+		       <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, false}, {var2, true}], <<"yay">>},
+		      {"If false or false ",
+		       <<"{% if var1 or var2 %}yay{% endif %}">>, [{var1, false}, {var2, false}], <<"">>}
+		     ]},
+     {"if equality", [
+		      {"If int equals number literal",
+		       <<"{% if var1 == 2 %}yay{% endif %}">>, [{var1, 2}], <<"yay">>},
+		      {"If int equals number literal (false)",
+		       <<"{% if var1 == 2 %}yay{% endif %}">>, [{var1, 3}], <<"">>},
+		      {"If string equals string literal",
+		       <<"{% if var1 == \"2\" %}yay{% endif %}">>, [{var1, "2"}], <<"yay">>},
+		      {"If string equals string literal (false)",
+		       <<"{% if var1 == \"2\" %}yay{% endif %}">>, [{var1, "3"}], <<"">>},
+		      {"If int not equals number literal",
+		       <<"{% if var1 != 2 %}yay{% endif %}">>, [{var1, 3}], <<"yay">>},
+		      {"If string not equals string literal",
+		       <<"{% if var1 != \"2\" %}yay{% endif %}">>, [{var1, "3"}], <<"yay">>},
+		      {"If filter result equals number literal",
+		       <<"{% if var1|length == 2 %}yay{% endif %}">>, [{var1, ["fo", "bo"]}], <<"yay">>},
+		      {"If filter result equals string literal",
+		       <<"{% if var1|capfirst == \"Foo\" %}yay{% endif %}">>, [{var1, "foo"}], <<"yay">>}
+		     ]},
+     {"if size comparison", [
+			     {"If int greater than number literal",
+			      <<"{% if var1 > 2 %}yay{% endif %}">>, [{var1, 3}], <<"yay">>},
+			     {"If int greater than negative number literal",
+			      <<"{% if var1 > -2 %}yay{% endif %}">>, [{var1, -1}], <<"yay">>},
+			     {"If int greater than number literal (false)",
+			      <<"{% if var1 > 2 %}yay{% endif %}">>, [{var1, 2}], <<"">>},
+
+			     {"If int greater than or equal to number literal",
+			      <<"{% if var1 >= 2 %}yay{% endif %}">>, [{var1, 3}], <<"yay">>},
+			     {"If int greater than or equal to number literal (2)",
+			      <<"{% if var1 >= 2 %}yay{% endif %}">>, [{var1, 2}], <<"yay">>},
+			     {"If int greater than or equal to number literal (false)",
+			      <<"{% if var1 >= 2 %}yay{% endif %}">>, [{var1, 1}], <<"">>},
+
+			     {"If int less than number literal",
+			      <<"{% if var1 < 2 %}yay{% endif %}">>, [{var1, 1}], <<"yay">>},
+			     {"If int less than number literal (false)",
+			      <<"{% if var1 < 2 %}yay{% endif %}">>, [{var1, 2}], <<"">>},
+
+			     {"If int less than or equal to number literal",
+			      <<"{% if var1 <= 2 %}yay{% endif %}">>, [{var1, 1}], <<"yay">>},
+			     {"If int less than or equal to number literal",
+			      <<"{% if var1 <= 2 %}yay{% endif %}">>, [{var1, 2}], <<"yay">>},
+			     {"If int less than or equal to number literal (false)",
+			      <<"{% if var1 <= 2 %}yay{% endif %}">>, [{var1, 3}], <<"">>}
+			    ]},
+     {"if complex bool", [
+			  {"If (true or false) and true",
+			   <<"{% if (var1 or var2) and var3 %}yay{% endif %}">>,
+			   [{var1, true}, {var2, false}, {var3, true}], <<"yay">>},
+			  {"If true or (false and true)",
+			   <<"{% if var1 or (var2 and var3) %}yay{% endif %}">>,
+			   [{var1, true}, {var2, false}, {var3, true}], <<"yay">>}
+			 ]},
+     {"for", [
+	      {"Simple loop",
+	       <<"{% for x in list %}{{ x }}{% endfor %}">>, [{'list', ["1", "2", "3"]}],
+	       <<"123">>},
+	      {"Reversed loop",
+	       <<"{% for x in list reversed %}{{ x }}{% endfor %}">>, [{'list', ["1", "2", "3"]}],
+	       <<"321">>},
+	      {"Expand list",
+	       <<"{% for x, y in list %}{{ x }},{{ y }}\n{% endfor %}">>, [{'list', [["X", "1"], ["X", "2"]]}],
+	       <<"X,1\nX,2\n">>},
+	      {"Expand tuple",
+	       <<"{% for x, y in list %}{{ x }},{{ y }}\n{% endfor %}">>, [{'list', [{"X", "1"}, {"X", "2"}]}],
+	       <<"X,1\nX,2\n">>},
+	      {"Resolve variable attribute",
+	       <<"{% for number in person.numbers %}{{ number }}\n{% endfor %}">>, [{person, [{numbers, ["411", "911"]}]}],
+	       <<"411\n911\n">>},
+	      {"Resolve nested variable attribute",
+	       <<"{% for number in person.home.numbers %}{{ number }}\n{% endfor %}">>, [{person, [{home, [{numbers, ["411", "911"]}]}]}],
+	       <<"411\n911\n">>},
+	      {"Counter0",
+	       <<"{% for number in numbers %}{{ forloop.counter0 }}. {{ number }}\n{% endfor %}">>,
+	       [{numbers, ["Zero", "One", "Two"]}], <<"0. Zero\n1. One\n2. Two\n">>},
+	      {"Counter",
+	       <<"{% for number in numbers %}{{ forloop.counter }}. {{ number }}\n{% endfor %}">>,
+	       [{numbers, ["One", "Two", "Three"]}], <<"1. One\n2. Two\n3. Three\n">>},
+	      {"Reverse Counter0",
+	       <<"{% for number in numbers %}{{ forloop.revcounter0 }}. {{ number }}\n{% endfor %}">>,
+	       [{numbers, ["Two", "One", "Zero"]}], <<"2. Two\n1. One\n0. Zero\n">>},
+	      {"Reverse Counter",
+	       <<"{% for number in numbers %}{{ forloop.revcounter }}. {{ number }}\n{% endfor %}">>,
+	       [{numbers, ["Three", "Two", "One"]}], <<"3. Three\n2. Two\n1. One\n">>},
+	      {"Counter \"first\"",
+	       <<"{% for number in numbers %}{% if forloop.first %}{{ number }}{% endif %}{% endfor %}">>,
+	       [{numbers, ["One", "Two", "Three"]}], <<"One">>},
+	      {"Counter \"last\"",
+	       <<"{% for number in numbers %}{% if forloop.last %}{{ number }}{% endif %}{% endfor %}">>,
+	       [{numbers, ["One", "Two", "Three"]}], <<"Three">>},
+	      {"Nested for loop",
+	       <<"{% for outer in list %}{% for inner in outer %}{{ inner }}\n{% endfor %}{% endfor %}">>,
+	       [{'list', [["Al", "Albert"], ["Jo", "Joseph"]]}],
+	       <<"Al\nAlbert\nJo\nJoseph\n">>},
+	      {"Access parent loop counters",
+	       <<"{% for outer in list %}{% for inner in outer %}({{ forloop.parentloop.counter0 }}, {{ forloop.counter0 }})\n{% endfor %}{% endfor %}">>,
+	       [{'list', [["One", "two"], ["One", "two"]]}], <<"(0, 0)\n(0, 1)\n(1, 0)\n(1, 1)\n">>},
+	      {"If changed",
+	       <<"{% for x in list %}{% ifchanged %}{{ x }}\n{% endifchanged %}{% endfor %}">>,
+	       [{'list', ["one", "two", "two", "three", "three", "three"]}], <<"one\ntwo\nthree\n">>},
+	      {"If changed/2",
+	       <<"{% for x, y in list %}{% ifchanged %}{{ x|upper }}{% endifchanged %}{% ifchanged %}{{ y|lower }}{% endifchanged %}\n{% endfor %}">>,
+	       [{'list', [["one", "a"], ["two", "A"], ["two", "B"], ["three", "b"], ["three", "c"], ["Three", "b"]]}], <<"ONEa\nTWO\nb\nTHREE\nc\nb\n">>},
+	      {"If changed/else",
+	       <<"{% for x in list %}{% ifchanged %}{{ x }}\n{% else %}foo\n{% endifchanged %}{% endfor %}">>,
+	       [{'list', ["one", "two", "two", "three", "three", "three"]}], <<"one\ntwo\nfoo\nthree\nfoo\nfoo\n">>},
+	      {"If changed/param",
+	       <<"{% for date in list %}{% ifchanged date.month %} {{ date.month }}:{{ date.day }}{% else %},{{ date.day }}{% endifchanged %}{% endfor %}\n">>,
+	       [{'list', [[{month,"Jan"},{day,1}],[{month,"Jan"},{day,2}],[{month,"Apr"},{day,10}],
+			  [{month,"Apr"},{day,11}],[{month,"May"},{day,4}]]}], 
+	       <<" Jan:1,2 Apr:10,11 May:4\n">>},
+	      {"If changed/param2",
+	       <<"{% for x, y in list %}{% ifchanged y|upper %}{{ x|upper }}{% endifchanged %}\n{% endfor %}">>,
+	       [{'list', [["one", "a"], ["two", "A"], ["two", "B"], ["three", "b"], ["three", "c"], ["Three", "b"]]}], <<"ONE\n\nTWO\n\nTHREE\nTHREE\n">>},
+	      {"If changed/param2 combined",
+	       <<"{% for x, y in list %}{% ifchanged x y|upper %}{{ x }}{% endifchanged %}\n{% endfor %}">>,
+	       [{'list', [["one", "a"], ["two", "A"], ["two", "B"], ["three", "b"], ["three", "B"], ["three", "c"]]}], <<"one\ntwo\ntwo\nthree\n\nthree\n">>},
+	      {"If changed/resolve",
+	       <<"{% for x in list %}{% ifchanged x.name|first %}{{ x.value }}{% endifchanged %}\n{% endfor %}">>,
+	       [{'list', [[{"name", ["nA","nB"]},{"value","1"}],[{"name", ["nA","nC"]},{"value","2"}],
+			  [{"name", ["nB","nC"]},{"value","3"}],[{"name", ["nB","nA"]},{"value","4"}]]}],
+	       <<"1\n\n3\n\n">>}
+	     ]},
+     {"for/empty", [
+		    {"Simple loop",
+		     <<"{% for x in list %}{{ x }}{% empty %}shucks{% endfor %}">>, [{'list', ["1", "2", "3"]}],
+		     <<"123">>},
+		    {"Simple loop (empty)",
+		     <<"{% for x in list %}{{ x }}{% empty %}shucks{% endfor %}">>, [{'list', []}],
+		     <<"shucks">>}
+		   ]},
+     {"ifequal", [
+		  {"Compare variable to literal",
+		   <<"{% ifequal var1 \"foo\" %}yay{% endifequal %}">>,
+		   [{var1, "foo"}], <<"yay">>},
+		  {"Compare variable to unequal literal",
+		   <<"{% ifequal var1 \"foo\" %}boo{% endifequal %}">>,
+		   [{var1, "bar"}], <<>>},
+		  {"Compare literal to variable",
+		   <<"{% ifequal \"foo\" var1 %}yay{% endifequal %}">>,
+		   [{var1, "foo"}], <<"yay">>},
+		  {"Compare literal to unequal variable",
+		   <<"{% ifequal \"foo\" var1 %}boo{% endifequal %}">>,
+		   [{var1, "bar"}], <<>>},
+		  {"Compare variable to literal (int string)",
+		   <<"{% ifequal var1 \"2\" %}yay{% else %}boo{% endifequal %}">>,
+		   [{var1, "2"}], <<"yay">>},
+		  {"Compare variable to literal (int)",
+		   <<"{% ifequal var1 2 %}yay{% else %}boo{% endifequal %}">>,
+		   [{var1, 2}], <<"yay">>},
+		  {"Compare variable to unequal literal (int)",
+		   <<"{% ifequal var1 2 %}boo{% else %}yay{% endifequal %}">>,
+		   [{var1, 3}], <<"yay">>},
+		  {"Compare variable to equal literal (atom)",
+		   <<"{% ifequal var1 \"foo\"%}yay{% endifequal %}">>,
+		   [{var1, foo}], <<"yay">>},
+		  {"Compare variable to unequal literal (atom)",
+		   <<"{% ifequal var1 \"foo\"%}yay{% else %}boo{% endifequal %}">>,
+		   [{var1, bar}], <<"boo">>}
+		 ]},
+     {"ifequal/else", [
+		       {"Compare variable to literal",
+			<<"{% ifequal var1 \"foo\" %}yay{% else %}boo{% endifequal %}">>,
+			[{var1, "foo"}], <<"yay">>},
+		       {"Compare variable to unequal literal",
+			<<"{% ifequal var1 \"foo\" %}boo{% else %}yay{% endifequal %}">>,
+			[{var1, "bar"}], <<"yay">>},
+		       {"Compare literal to variable",
+			<<"{% ifequal \"foo\" var1 %}yay{% else %}boo{% endifequal %}">>,
+			[{var1, "foo"}], <<"yay">>},
+		       {"Compare literal to unequal variable",
+			<<"{% ifequal \"foo\" var1 %}boo{% else %}yay{% endifequal %}">>,
+			[{var1, "bar"}], <<"yay">>}
+		      ]},
+     {"ifnotequal", [
+		     {"Compare variable to literal",
+		      <<"{% ifnotequal var1 \"foo\" %}boo{% endifnotequal %}">>,
+		      [{var1, "foo"}], <<>>},
+		     {"Compare variable to unequal literal",
+		      <<"{% ifnotequal var1 \"foo\" %}yay{% endifnotequal %}">>,
+		      [{var1, "bar"}], <<"yay">>},
+		     {"Compare literal to variable",
+		      <<"{% ifnotequal \"foo\" var1 %}boo{% endifnotequal %}">>,
+		      [{var1, "foo"}], <<>>},
+		     {"Compare literal to unequal variable",
+		      <<"{% ifnotequal \"foo\" var1 %}yay{% endifnotequal %}">>,
+		      [{var1, "bar"}], <<"yay">>}
+		    ]},
+     {"ifnotequal/else", [
+			  {"Compare variable to literal",
+			   <<"{% ifnotequal var1 \"foo\" %}boo{% else %}yay{% endifnotequal %}">>,
+			   [{var1, "foo"}], <<"yay">>},
+			  {"Compare variable to unequal literal",
+			   <<"{% ifnotequal var1 \"foo\" %}yay{% else %}boo{% endifnotequal %}">>,
+			   [{var1, "bar"}], <<"yay">>},
+			  {"Compare literal to variable",
+			   <<"{% ifnotequal \"foo\" var1 %}boo{% else %}yay{% endifnotequal %}">>,
+			   [{var1, "foo"}], <<"yay">>},
+			  {"Compare literal to unequal variable",
+			   <<"{% ifnotequal \"foo\" var1 %}yay{% else %}boo{% endifnotequal %}">>,
+			   [{var1, "bar"}], <<"yay">>}
+			 ]},
+     {"filter tag", [
+		     {"Apply a filter",
+		      <<"{% filter escape %}&{% endfilter %}">>, [], <<"&amp;">>},
+		     {"Chained filters",
+		      <<"{% filter linebreaksbr|escape %}\n{% endfilter %}">>, [], <<"&lt;br /&gt;">>}
+		    ]},
+     {"filters", [
+		  {"Filter a literal",
+		   <<"{{ \"pop\"|capfirst }}">>, [],
+		   <<"Pop">>},
+		  {"Filters applied in order",
+		   <<"{{ var1|force_escape|length }}">>, [{var1, <<"&">>}],
+		   <<"5">>},
+		  {"Escape is applied last",
+		   <<"{{ var1|escape|linebreaksbr }}">>, [{var1, <<"\n">>}],
+		   <<"&lt;br /&gt;">>},
+		  {"add; lhs number, rhs number",
+		   <<"{{ one|add:4}}">>, [{one, 1}],
+		   <<"5">>},
+		  {"add; lhs numeric string, rhs number",
+		   <<"{{ one|add:4}}">>, [{one, "1"}],
+		   <<"5">>},
+		  {"add; lhs number, rhs numeric string",
+		   <<"{{ one|add:'4'}}">>, [{one, 1}],
+		   <<"5">>},
+		  {"add; lhs non-numeric string, rhs number",
+		   <<"{{ one|add:4}}">>, [{one, "foo"}],
+		   <<"foo4">>},
+		  {"add; lhs number, rhs non-numeric string",
+		   <<"{{ one|add:'foo'}}">>, [{one, 1}],
+		   <<"1foo">>},
+		  {"add; lhs non-numeric string, rhs non-numeric string",
+		   <<"{{ one|add:'bar'}}">>, [{one, "foo"}],
+		   <<"foobar">>},
+		  {"add; lhs numeric string, rhs numeric string",
+		   <<"{{ one|add:'4'}}">>, [{one, "1"}],
+		   <<"5">>},
+		  {"|addslashes",
+		   <<"{{ var1|addslashes }}">>, [{var1, "Jimmy's \"great\" meats'n'things"}],
+		   <<"Jimmy\\'s \\\"great\\\" meats\\'n\\'things">>},
+		  {"|capfirst",
+		   <<"{{ var1|capfirst }}">>, [{var1, "dana boyd"}],
+		   <<"Dana boyd">>},
+		  {"|center:10",
+		   <<"{{ var1|center:10 }}">>, [{var1, "MB"}],
+		   <<"    MB    ">>},
+		  {"|center:1",
+		   <<"{{ var1|center:1 }}">>, [{var1, "KBR"}],
+		   <<"B">>},
+		  {"|cut:\" \"",
+		   <<"{{ var1|cut:\" \" }}">>, [{var1, "String with spaces"}],
+		   <<"Stringwithspaces">>},
+		  {"|date 1",
                    <<"{{ var1|date:\"jS F Y H:i\" }}">>,
                    [{var1, {1975,7,24}}],
                    <<"24th July 1975 00:00">>},
-                {"|date 2",
+		  {"|date 2",
                    <<"{{ var1|date:\"jS F Y H:i\" }}">>,
                    [{var1, {{1975,7,24}, {7,13,1}}}],
                    <<"24th July 1975 07:13">>},
-                {"|date 3",
+		  {"|date 3",
                    <<"{{ var1|date }}">>,
                    [{var1, {{1975,7,24}, {7,13,1}}}],
                    <<"July 24, 1975">>},
-                {"|default:\"foo\" 1",
+		  {"|default:\"foo\" 1",
                    <<"{{ var1|default:\"foo\" }}">>, [], <<"foo">>},
-                {"|default:\"foo\" 2",
-                    <<"{{ var1|default:\"foo\" }}">>, [{var1, "bar"}], <<"bar">>},
-                {"|default:\"foo\" 3",
-                    <<"{{ var1|default:\"foo\" }}">>, [{var1, "0"}], <<"foo">>},
-                {"|default_if_none:\"foo\"",
+		  {"|default:\"foo\" 2",
+		   <<"{{ var1|default:\"foo\" }}">>, [{var1, "bar"}], <<"bar">>},
+		  {"|default:\"foo\" 3",
+		   <<"{{ var1|default:\"foo\" }}">>, [{var1, "0"}], <<"foo">>},
+		  {"|default_if_none:\"foo\"",
                    <<"{{ var1|default_if_none:\"foo\" }}">>, [], <<"foo">>},
-                {"|default_if_none:\"foo\" 2",
-                    <<"{{ var1|default_if_none:\"foo\" }}">>, [{var1, "bar"}], <<"bar">>},
-		{"|dictsort 1",
-		 <<"{{ var1|dictsort:\"foo\" }}">>,
-		 [{var1,[[{foo,2}],[{foo,1}]]}], <<"{foo,1}{foo,2}">>},
-	        {"|dictsort 2",
-		 <<"{{ var1|dictsort:\"foo.bar\" }}">>,
-		 [{var1,[[{foo,[{bar,2}]}],[{foo,[{bar,1}]}]]}],
-		 <<"{foo,[{bar,1}]}{foo,[{bar,2}]}">>},
-                {"|divisibleby:\"3\"",
-                    <<"{% if var1|divisibleby:\"3\" %}yay{% endif %}">>, [{var1, 21}], <<"yay">>},
-                {"|divisibleby:\"3\"",
-                    <<"{% if var1|divisibleby:\"3\" %}yay{% endif %}">>, [{var1, 22}], <<"">>},
-                {"|escape",
-                    <<"{% autoescape on %}{{ var1|escape|escape|escape }}{% endautoescape %}">>, [{var1, ">&1"}], <<"&gt;&amp;1">>},
-                {"|escapejs",
-                    <<"{{ var1|escapejs }}">>, [{var1, "testing\r\njavascript 'string\" <b>escaping</b>"}],
-                    <<"testing\\u000D\\u000Ajavascript \\u0027string\\u0022 \\u003Cb\\u003Eescaping\\u003C/b\\u003E">>},
-                {"|filesizeformat (bytes)",
-                    <<"{{ var1|filesizeformat }}">>, [{var1, 1023}], <<"1023 bytes">>},
-                {"|filesizeformat (KB)",
-                    <<"{{ var1|filesizeformat }}">>, [{var1, 3487}], <<"3.4 KB">>},
-                {"|filesizeformat (MB)",
-                    <<"{{ var1|filesizeformat }}">>, [{var1, 6277098}], <<"6.0 MB">>},
-                {"|filesizeformat (GB)",
-                    <<"{{ var1|filesizeformat }}">>, [{var1, 1024 * 1024 * 1024}], <<"1.0 GB">>},
-                {"|first",
-                    <<"{{ var1|first }}">>, [{var1, "James"}],
-                    <<"J">>},
-                {"|fix_ampersands",
-                    <<"{{ var1|fix_ampersands }}">>, [{var1, "Ben & Jerry's"}],
-                    <<"Ben &amp; Jerry's">>},
-               
-               {"|floatformat:\"-1\"",
-                    <<"{{ var1|floatformat:\"-1\" }}">>, [{var1, 34.23234}],
-                    <<"34.2">>},
-%%         ?assertEqual( "", erlydtl_filters:floatformat(,)),
-%%         ?assertEqual( "34", erlydtl_filters:floatformat(34.00000,-1)),
-%%         ?assertEqual( "34.3", erlydtl_filters:floatformat(34.26000,-1)),
-%%         ?assertEqual( "34.232", erlydtl_filters:floatformat(34.23234,3)),
-%%         ?assertEqual( "34.000", erlydtl_filters:floatformat(34.00000,3)),
-%%         ?assertEqual( "34.260", erlydtl_filters:floatformat(34.26000,3)),
-%%         ?assertEqual( "34.232", erlydtl_filters:floatformat(34.23234,-3)),
-%%         ?assertEqual( "34", erlydtl_filters:floatformat(34.00000,-3)),
-%%         ?assertEqual( "34.260", erlydtl_filters:floatformat(34.26000,-3)).
-                {"|force_escape",
-                    <<"{{ var1|force_escape }}">>, [{var1, "Ben & Jerry's <=> \"The World's Best Ice Cream\""}],
-                    <<"Ben &amp; Jerry&#039;s &lt;=&gt; &quot;The World&#039;s Best Ice Cream&quot;">>},
-                {"|format_integer",
-                    <<"{{ var1|format_integer }}">>, [{var1, 28}], <<"28">>},
-                {"|format_number 1",
-                    <<"{{ var1|format_number }}">>, [{var1, 28}], <<"28">>},
-                {"|format_number 2",
-                    <<"{{ var1|format_number }}">>, [{var1, 23.77}], <<"23.77">>},
-                {"|format_number 3",
-                    <<"{{ var1|format_number }}">>, [{var1, "28.77"}], <<"28.77">>},
-                {"|format_number 4",
-                    <<"{{ var1|format_number }}">>, [{var1, "23.77"}], <<"23.77">>},
-                {"|format_number 5",
-                    <<"{{ var1|format_number }}">>, [{var1, fun() -> 29 end}], <<"29">>},
-                {"|format_number 6",
-                    <<"{{ var1|format_number }}">>, [{var1, fun() -> fun() -> 31 end end}], <<"31">>},
-                {"|get_digit:\"2\"",
-                    <<"{{ var1|get_digit:\"2\" }}">>, [{var1, 42}], <<"4">>},
-                {"|iriencode",
-                    <<"{{ url|iriencode }}">>, [{url, "You #$*@!!"}], <<"You+#$*@!!">>},
-                {"|join:\", \" (list)",
-                    <<"{{ var1|join:\", \" }}">>, [{var1, ["Liberte", "Egalite", "Fraternite"]}],
-                    <<"Liberte, Egalite, Fraternite">>},
-                {"|join:\", \" (binary)",
-                    <<"{{ var1|join:\", \" }}">>, [{var1, [<<"Liberte">>, "Egalite", <<"Fraternite">>]}],
-                    <<"Liberte, Egalite, Fraternite">>},
-                {"|last",
-                    <<"{{ var1|last }}">>, [{var1, "XYZ"}],
-                    <<"Z">>},
-                {"|length",
-                    <<"{{ var1|length }}">>, [{var1, "antidisestablishmentarianism"}],
-                    <<"28">>},
-                {"|linebreaks",
-                    <<"{{ var1|linebreaks }}">>, [{var1, "Joel\nis a slug"}],
-                    <<"<p>Joel<br />is a slug</p>">>},               
-                {"|linebreaks",
-                    <<"{{ var1|linebreaks }}">>, [{var1, "Joel\n\n\n\nis a slug"}],
-                    <<"<p>Joel</p><p>is a slug</p>">>},               
-                {"|linebreaks",
-                    <<"{{ var1|linebreaks }}">>, [{var1, "Joel\n\nis a \nslug"}],
-                    <<"<p>Joel</p><p>is a <br />slug</p>">>},               
-                {"|linebreaksbr",
-                    <<"{{ var1|linebreaksbr }}">>, [{var1, "One\nTwo\n\nThree\n\n\n"}],
-                    <<"One<br />Two<br /><br />Three<br /><br /><br />">>},
-                {"|linebreaksbr",
-                    <<"{{ \"One\\nTwo\\n\\nThree\\n\\n\\n\"|linebreaksbr }}">>, [],
-                    <<"One<br />Two<br /><br />Three<br /><br /><br />">>},             
-                {"|linenumbers",
-                    <<"{{ var1|linenumbers }}">>, [{var1, "a\nb\nc"}],
-                    <<"1. a\n2. b\n3. c">>},
-                {"|linenumbers",
-                    <<"{{ var1|linenumbers }}">>, [{var1, "a"}],
-                    <<"1. a">>},
-                {"|linenumbers",
-                    <<"{{ var1|linenumbers }}">>, [{var1, "a\n"}],
-                    <<"1. a\n2. ">>},
-                {"|ljust:10",
-                    <<"{{ var1|ljust:10 }}">>, [{var1, "Gore"}],
-                    <<"Gore      ">>},
-                {"|lower",
-                    <<"{{ var1|lower }}">>, [{var1, "E. E. Cummings"}],
-                    <<"e. e. cummings">>},
-                {"|makelist",
-                    <<"{{ list|make_list }}">>, [{list, "Joel"}],
-                    <<"J","o","e","l">>},
-                {"|pluralize",
-                    <<"{{ num|pluralize }}">>, [{num, 1}],
-                    <<"">>},
-                {"|pluralize",
-                    <<"{{ num|pluralize }}">>, [{num, 2}],
-                    <<"s">>},
-                {"|pluralize:\"s\"",
-                    <<"{{ num|pluralize }}">>, [{num, 1}],
-                    <<"">>},
-                {"|pluralize:\"s\"",
-                    <<"{{ num|pluralize }}">>, [{num, 2}],
-                    <<"s">>},
-                {"|pluralize:\"y,es\" (list)",
-                    <<"{{ num|pluralize:\"y,es\" }}">>, [{num, 1}],
-                    <<"y">>},
-                {"|pluralize:\"y,es\" (list)",
-                    <<"{{ num|pluralize:\"y,es\" }}">>, [{num, 2}],
-                    <<"es">>},
-                {"|random",
-                    <<"{{ var1|random }}">>, [{var1, ["foo", "foo", "foo"]}],
-                    <<"foo">>},
-                {"|removetags:\"b span\"",
-                    <<"{{ var1|removetags:\"b span\" }}">>, [{var1, "<B>Joel</B> <button>is</button> a <span>slug</span>"}],
-                    <<"<B>Joel</B> <button>is</button> a slug">>},
-                {"|rjust:10",
-                    <<"{{ var1|rjust:10 }}">>, [{var1, "Bush"}],
-                    <<"      Bush">>},
-                {"|safe",
-                    <<"{% autoescape on %}{{ var1|safe|escape }}{% endautoescape %}">>, [{var1, "&"}],
-                    <<"&">>},
-                %%python/django slice is zero based, erlang lists are 1 based
-                %%first number included, second number not
-                %%negative numbers are allowed
-               %%regex to convert from erlydtl_filters_tests:
-                % for slice: \?assert.*\( \[(.*)\], erlydtl_filters:(.*)\((.*),"(.*)"\)\),
-                % {"|slice:\"$4\"", <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],<<$1>>},
-               % \t\t{"|slice:\"$4\"",\n\t\t\t\t\t <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],\n\t\t\t\t\t<<$1>>},
-               %
-               % for stringformat: 
-               % \?assert.*\( (.*), erlydtl_filters:(.*)\((.*), "(.*)"\) \)
-               % \t\t{"|stringformat:\"$4\"",\n\t\t\t\t\t <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],\n\t\t\t\t\t<<$1>>}
-                 
-                {"|slice:\":\"",
-                    <<"{{ var|slice:\":\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8,9>>},
-                {"|slice:\"1\"", 
-                    <<"{{ var|slice:\"1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<"2">>},
-                {"|slice:\"100\"", 
-                    <<"{{ var|slice:\"100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<"indexError">>},
-                {"|slice:\"-1\"", 
-                    <<"{{ var|slice:\"-1\" }}">>, [{var, ["a","b","c","d","e","f","g","h","i"]}],
-                    <<"i">>},
-                {"|slice:\"-1\"", 
-                    <<"{{ var|slice:\"-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<"9">>},
-                {"|slice:\"-100\"", 
-                    <<"{{ var|slice:\"-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<"indexError">>},
-                {"|slice:\"1:\"",
-                     <<"{{ var|slice:\"1:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<2,3,4,5,6,7,8,9>>},
-                {"|slice:\"100:\"",
-                     <<"{{ var|slice:\"100:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"-1:\"",
-                     <<"{{ var|slice:\"-1:\" }}">>, [{var, ["a","b","c","d","e","f","h","i","j"]}],
-                    <<"j">>},
-                {"|slice:\"-1:\"",
-                     <<"{{ var|slice:\"-1:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<9>>},
-                {"|slice:\"-100:\"",
-                     <<"{{ var|slice:\"-100:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8,9>>},
-       
-                {"|slice:\":1\"",
-                     <<"{{ var|slice:\":1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1>>},
-                {"|slice:\":100\"",
-                     <<"{{ var|slice:\":100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8,9>>},
-                {"|slice:\":-1\"",
-                     <<"{{ var|slice:\":-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8>>},
-                {"|slice:\":-100\"",
-                     <<"{{ var|slice:\":-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-       
-                {"|slice:\"-1:-1\"",
-                     <<"{{ var|slice:\"-1:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"1:1\"",
-                     <<"{{ var|slice:\"1:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"1:-1\"",
-                     <<"{{ var|slice:\"1:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<2,3,4,5,6,7,8>>},
-                {"|slice:\"-1:1\"",
-                     <<"{{ var|slice:\"-1:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-        
-                {"|slice:\"-100:-100\"",
-                     <<"{{ var|slice:\"-100:-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"100:100\"",
-                     <<"{{ var|slice:\"100:100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"100:-100\"",
-                     <<"{{ var|slice:\"100:-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"-100:100\"",
-                     <<"{{ var|slice:\"-100:100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8,9>>},
-        
-       
-                {"|slice:\"1:3\"",
-                     <<"{{ var|slice:\"1:3\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<2,3>>},
-        
-                {"|slice:\"::\"",
-                     <<"{{ var|slice:\"::\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8,9>>},
-                {"|slice:\"1:9:1\"",
-                     <<"{{ var|slice:\"1:9:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<2,3,4,5,6,7,8,9>>},
-                {"|slice:\"10:1:-1\"",
-                     <<"{{ var|slice:\"10:1:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<9,8,7,6,5,4,3>>},
-                {"|slice:\"-111:-1:1\"",
-                     <<"{{ var|slice:\"-111:-1:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8>>},
-        
-                {"|slice:\"-111:-111:1\"",
-                     <<"{{ var|slice:\"-111:-111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"111:111:1\"",
-                     <<"{{ var|slice:\"111:111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"-111:111:1\"",
-                     <<"{{ var|slice:\"-111:111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<1,2,3,4,5,6,7,8,9>>},
-                {"|slice:\"111:-111:1\"",
-                     <<"{{ var|slice:\"111:-111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-        
-                {"|slice:\"-111:-111:-1\"",
-                     <<"{{ var|slice:\"-111:-111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"111:111:-1\"",
-                     <<"{{ var|slice:\"111:111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"-111:111:-1\"",
-                     <<"{{ var|slice:\"-111:111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<>>},
-                {"|slice:\"111:-111:-1\"",
-                     <<"{{ var|slice:\"111:-111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
-                    <<9,8,7,6,5,4,3,2,1>>},              {"|phone2numeric",
-                    <<"{{ var1|phone2numeric }}">>, [{var1, "1-800-COLLECT"}],
-                    <<"1-800-2655328">>},
-                {"|slugify",
-                    <<"{{ var1|slugify }}">>, [{var1, "What The $#_! Was He Thinking?"}],
-                    <<"what-the-_-was-he-thinking">>},
-                    {"|slice:\"s\"",
-                     <<"{{ var|stringformat:\"s\" }}">>, [{var, "test"}],
-                    <<"test">>},
-                        {"|stringformat:\"s\"",
-                     <<"{{ var|stringformat:\"s\" }}">>, [{var, "test"}],
-                    <<"test">>},
-                {"|stringformat:\"s\"",
-                     <<"{{ var|stringformat:\"s\" }}">>, [{var, "1"}],
-                    <<"1">>},
-                {"|stringformat:\"s\"",
-                     <<"{{ var|stringformat:\"s\" }}">>, [{var, "test"}],
-                    <<"test">>},
-                {"|stringformat:\"10s\"",
-                     <<"{{ var|stringformat:\"10s\" }}">>, [{var, "test"}],
-                    <<"      test">>},
-                {"|stringformat:\"-10s\"",
-                     <<"{{ var|stringformat:\"-10s\" }}">>, [{var, "test"}],
-                    <<"test      ">>},
-        
-                {"|stringformat:\"d\"",
-                     <<"{{ var|stringformat:\"d\" }}">>, [{var, "90"}],
-                    <<"90">>},  
-                {"|stringformat:\"10d\"",
-                     <<"{{ var|stringformat:\"10d\" }}">>, [{var, "90"}],
-                    <<"        90">>},
-                {"|stringformat:\"-10d\"",
-                     <<"{{ var|stringformat:\"-10d\" }}">>, [{var, "90"}],
-                    <<"90        ">>},
-                {"|stringformat:\"i\"",
-                     <<"{{ var|stringformat:\"i\" }}">>, [{var, "90"}],
-                    <<"90">>},  
-                {"|stringformat:\"10i\"",
-                     <<"{{ var|stringformat:\"10i\" }}">>, [{var, "90"}],
-                    <<"        90">>},
-                {"|stringformat:\"-10i\"",
-                     <<"{{ var|stringformat:\"-10i\" }}">>, [{var, "90"}],
-                    <<"90        ">>},
-                {"|stringformat:\"0.2d\"",
-                     <<"{{ var|stringformat:\"0.2d\" }}">>, [{var, "9"}],
-                    <<"09">>},    
-                {"|stringformat:\"10.4d\"",
-                     <<"{{ var|stringformat:\"10.4d\" }}">>, [{var, "9"}],
-                    <<"      0009">>},
-                {"|stringformat:\"-10.4d\"",
-                     <<"{{ var|stringformat:\"-10.4d\" }}">>, [{var, "9"}],
-                    <<"0009      ">>},
+		  {"|default_if_none:\"foo\" 2",
+		   <<"{{ var1|default_if_none:\"foo\" }}">>, [{var1, "bar"}], <<"bar">>},
+		  {"|dictsort 1",
+		   <<"{{ var1|dictsort:\"foo\" }}">>,
+		   [{var1,[[{foo,2}],[{foo,1}]]}], <<"{foo,1}{foo,2}">>},
+		  {"|dictsort 2",
+		   <<"{{ var1|dictsort:\"foo.bar\" }}">>,
+		   [{var1,[[{foo,[{bar,2}]}],[{foo,[{bar,1}]}]]}],
+		   <<"{foo,[{bar,1}]}{foo,[{bar,2}]}">>},
+		  {"|divisibleby:\"3\"",
+		   <<"{% if var1|divisibleby:\"3\" %}yay{% endif %}">>, [{var1, 21}], <<"yay">>},
+		  {"|divisibleby:\"3\"",
+		   <<"{% if var1|divisibleby:\"3\" %}yay{% endif %}">>, [{var1, 22}], <<"">>},
+		  {"|escape",
+		   <<"{% autoescape on %}{{ var1|escape|escape|escape }}{% endautoescape %}">>, [{var1, ">&1"}], <<"&gt;&amp;1">>},
+		  {"|escapejs",
+		   <<"{{ var1|escapejs }}">>, [{var1, "testing\r\njavascript 'string\" <b>escaping</b>"}],
+		   <<"testing\\u000D\\u000Ajavascript \\u0027string\\u0022 \\u003Cb\\u003Eescaping\\u003C/b\\u003E">>},
+		  {"|filesizeformat (bytes)",
+		   <<"{{ var1|filesizeformat }}">>, [{var1, 1023}], <<"1023 bytes">>},
+		  {"|filesizeformat (KB)",
+		   <<"{{ var1|filesizeformat }}">>, [{var1, 3487}], <<"3.4 KB">>},
+		  {"|filesizeformat (MB)",
+		   <<"{{ var1|filesizeformat }}">>, [{var1, 6277098}], <<"6.0 MB">>},
+		  {"|filesizeformat (GB)",
+		   <<"{{ var1|filesizeformat }}">>, [{var1, 1024 * 1024 * 1024}], <<"1.0 GB">>},
+		  {"|first",
+		   <<"{{ var1|first }}">>, [{var1, "James"}],
+		   <<"J">>},
+		  {"|fix_ampersands",
+		   <<"{{ var1|fix_ampersands }}">>, [{var1, "Ben & Jerry's"}],
+		   <<"Ben &amp; Jerry's">>},
+
+		  {"|floatformat:\"-1\"",
+		   <<"{{ var1|floatformat:\"-1\" }}">>, [{var1, 34.23234}],
+		   <<"34.2">>},
+		  %%         ?assertEqual( "", erlydtl_filters:floatformat(,)),
+		  %%         ?assertEqual( "34", erlydtl_filters:floatformat(34.00000,-1)),
+		  %%         ?assertEqual( "34.3", erlydtl_filters:floatformat(34.26000,-1)),
+		  %%         ?assertEqual( "34.232", erlydtl_filters:floatformat(34.23234,3)),
+		  %%         ?assertEqual( "34.000", erlydtl_filters:floatformat(34.00000,3)),
+		  %%         ?assertEqual( "34.260", erlydtl_filters:floatformat(34.26000,3)),
+		  %%         ?assertEqual( "34.232", erlydtl_filters:floatformat(34.23234,-3)),
+		  %%         ?assertEqual( "34", erlydtl_filters:floatformat(34.00000,-3)),
+		  %%         ?assertEqual( "34.260", erlydtl_filters:floatformat(34.26000,-3)).
+		  {"|force_escape",
+		   <<"{{ var1|force_escape }}">>, [{var1, "Ben & Jerry's <=> \"The World's Best Ice Cream\""}],
+		   <<"Ben &amp; Jerry&#039;s &lt;=&gt; &quot;The World&#039;s Best Ice Cream&quot;">>},
+		  {"|format_integer",
+		   <<"{{ var1|format_integer }}">>, [{var1, 28}], <<"28">>},
+		  {"|format_number 1",
+		   <<"{{ var1|format_number }}">>, [{var1, 28}], <<"28">>},
+		  {"|format_number 2",
+		   <<"{{ var1|format_number }}">>, [{var1, 23.77}], <<"23.77">>},
+		  {"|format_number 3",
+		   <<"{{ var1|format_number }}">>, [{var1, "28.77"}], <<"28.77">>},
+		  {"|format_number 4",
+		   <<"{{ var1|format_number }}">>, [{var1, "23.77"}], <<"23.77">>},
+		  {"|format_number 5",
+		   <<"{{ var1|format_number }}">>, [{var1, fun() -> 29 end}], <<"29">>},
+		  {"|format_number 6",
+		   <<"{{ var1|format_number }}">>, [{var1, fun() -> fun() -> 31 end end}], <<"31">>},
+		  {"|get_digit:\"2\"",
+		   <<"{{ var1|get_digit:\"2\" }}">>, [{var1, 42}], <<"4">>},
+		  {"|iriencode",
+		   <<"{{ url|iriencode }}">>, [{url, "You #$*@!!"}], <<"You+#$*@!!">>},
+		  {"|join:\", \" (list)",
+		   <<"{{ var1|join:\", \" }}">>, [{var1, ["Liberte", "Egalite", "Fraternite"]}],
+		   <<"Liberte, Egalite, Fraternite">>},
+		  {"|join:\", \" (binary)",
+		   <<"{{ var1|join:\", \" }}">>, [{var1, [<<"Liberte">>, "Egalite", <<"Fraternite">>]}],
+		   <<"Liberte, Egalite, Fraternite">>},
+		  {"|last",
+		   <<"{{ var1|last }}">>, [{var1, "XYZ"}],
+		   <<"Z">>},
+		  {"|length",
+		   <<"{{ var1|length }}">>, [{var1, "antidisestablishmentarianism"}],
+		   <<"28">>},
+		  {"|linebreaks",
+		   <<"{{ var1|linebreaks }}">>, [{var1, "Joel\nis a slug"}],
+		   <<"<p>Joel<br />is a slug</p>">>},               
+		  {"|linebreaks",
+		   <<"{{ var1|linebreaks }}">>, [{var1, "Joel\n\n\n\nis a slug"}],
+		   <<"<p>Joel</p><p>is a slug</p>">>},               
+		  {"|linebreaks",
+		   <<"{{ var1|linebreaks }}">>, [{var1, "Joel\n\nis a \nslug"}],
+		   <<"<p>Joel</p><p>is a <br />slug</p>">>},               
+		  {"|linebreaksbr",
+		   <<"{{ var1|linebreaksbr }}">>, [{var1, "One\nTwo\n\nThree\n\n\n"}],
+		   <<"One<br />Two<br /><br />Three<br /><br /><br />">>},
+		  {"|linebreaksbr",
+		   <<"{{ \"One\\nTwo\\n\\nThree\\n\\n\\n\"|linebreaksbr }}">>, [],
+		   <<"One<br />Two<br /><br />Three<br /><br /><br />">>},             
+		  {"|linenumbers",
+		   <<"{{ var1|linenumbers }}">>, [{var1, "a\nb\nc"}],
+		   <<"1. a\n2. b\n3. c">>},
+		  {"|linenumbers",
+		   <<"{{ var1|linenumbers }}">>, [{var1, "a"}],
+		   <<"1. a">>},
+		  {"|linenumbers",
+		   <<"{{ var1|linenumbers }}">>, [{var1, "a\n"}],
+		   <<"1. a\n2. ">>},
+		  {"|ljust:10",
+		   <<"{{ var1|ljust:10 }}">>, [{var1, "Gore"}],
+		   <<"Gore      ">>},
+		  {"|lower",
+		   <<"{{ var1|lower }}">>, [{var1, "E. E. Cummings"}],
+		   <<"e. e. cummings">>},
+		  {"|makelist",
+		   <<"{{ list|make_list }}">>, [{list, "Joel"}],
+		   <<"J","o","e","l">>},
+		  {"|pluralize",
+		   <<"{{ num|pluralize }}">>, [{num, 1}],
+		   <<"">>},
+		  {"|pluralize",
+		   <<"{{ num|pluralize }}">>, [{num, 2}],
+		   <<"s">>},
+		  {"|pluralize:\"s\"",
+		   <<"{{ num|pluralize }}">>, [{num, 1}],
+		   <<"">>},
+		  {"|pluralize:\"s\"",
+		   <<"{{ num|pluralize }}">>, [{num, 2}],
+		   <<"s">>},
+		  {"|pluralize:\"y,es\" (list)",
+		   <<"{{ num|pluralize:\"y,es\" }}">>, [{num, 1}],
+		   <<"y">>},
+		  {"|pluralize:\"y,es\" (list)",
+		   <<"{{ num|pluralize:\"y,es\" }}">>, [{num, 2}],
+		   <<"es">>},
+		  {"|random",
+		   <<"{{ var1|random }}">>, [{var1, ["foo", "foo", "foo"]}],
+		   <<"foo">>},
+		  {"|removetags:\"b span\"",
+		   <<"{{ var1|removetags:\"b span\" }}">>, [{var1, "<B>Joel</B> <button>is</button> a <span>slug</span>"}],
+		   <<"<B>Joel</B> <button>is</button> a slug">>},
+		  {"|rjust:10",
+		   <<"{{ var1|rjust:10 }}">>, [{var1, "Bush"}],
+		   <<"      Bush">>},
+		  {"|safe",
+		   <<"{% autoescape on %}{{ var1|safe|escape }}{% endautoescape %}">>, [{var1, "&"}],
+		   <<"&">>},
+		  %%python/django slice is zero based, erlang lists are 1 based
+		  %%first number included, second number not
+		  %%negative numbers are allowed
+		  %%regex to convert from erlydtl_filters_tests:
+						% for slice: \?assert.*\( \[(.*)\], erlydtl_filters:(.*)\((.*),"(.*)"\)\),
+						% {"|slice:\"$4\"", <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],<<$1>>},
+						% \t\t{"|slice:\"$4\"",\n\t\t\t\t\t <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],\n\t\t\t\t\t<<$1>>},
+						%
+						% for stringformat: 
+						% \?assert.*\( (.*), erlydtl_filters:(.*)\((.*), "(.*)"\) \)
+						% \t\t{"|stringformat:\"$4\"",\n\t\t\t\t\t <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],\n\t\t\t\t\t<<$1>>}
+
+		  {"|slice:\":\"",
+		   <<"{{ var|slice:\":\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8,9>>},
+		  {"|slice:\"1\"", 
+		   <<"{{ var|slice:\"1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<"2">>},
+		  {"|slice:\"100\"", 
+		   <<"{{ var|slice:\"100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<"indexError">>},
+		  {"|slice:\"-1\"", 
+		   <<"{{ var|slice:\"-1\" }}">>, [{var, ["a","b","c","d","e","f","g","h","i"]}],
+		   <<"i">>},
+		  {"|slice:\"-1\"", 
+		   <<"{{ var|slice:\"-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<"9">>},
+		  {"|slice:\"-100\"", 
+		   <<"{{ var|slice:\"-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<"indexError">>},
+		  {"|slice:\"1:\"",
+		   <<"{{ var|slice:\"1:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<2,3,4,5,6,7,8,9>>},
+		  {"|slice:\"100:\"",
+		   <<"{{ var|slice:\"100:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"-1:\"",
+		   <<"{{ var|slice:\"-1:\" }}">>, [{var, ["a","b","c","d","e","f","h","i","j"]}],
+		   <<"j">>},
+		  {"|slice:\"-1:\"",
+		   <<"{{ var|slice:\"-1:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<9>>},
+		  {"|slice:\"-100:\"",
+		   <<"{{ var|slice:\"-100:\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8,9>>},
+
+		  {"|slice:\":1\"",
+		   <<"{{ var|slice:\":1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1>>},
+		  {"|slice:\":100\"",
+		   <<"{{ var|slice:\":100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8,9>>},
+		  {"|slice:\":-1\"",
+		   <<"{{ var|slice:\":-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8>>},
+		  {"|slice:\":-100\"",
+		   <<"{{ var|slice:\":-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+
+		  {"|slice:\"-1:-1\"",
+		   <<"{{ var|slice:\"-1:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"1:1\"",
+		   <<"{{ var|slice:\"1:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"1:-1\"",
+		   <<"{{ var|slice:\"1:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<2,3,4,5,6,7,8>>},
+		  {"|slice:\"-1:1\"",
+		   <<"{{ var|slice:\"-1:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+
+		  {"|slice:\"-100:-100\"",
+		   <<"{{ var|slice:\"-100:-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"100:100\"",
+		   <<"{{ var|slice:\"100:100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"100:-100\"",
+		   <<"{{ var|slice:\"100:-100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"-100:100\"",
+		   <<"{{ var|slice:\"-100:100\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8,9>>},
+
+
+		  {"|slice:\"1:3\"",
+		   <<"{{ var|slice:\"1:3\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<2,3>>},
+
+		  {"|slice:\"::\"",
+		   <<"{{ var|slice:\"::\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8,9>>},
+		  {"|slice:\"1:9:1\"",
+		   <<"{{ var|slice:\"1:9:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<2,3,4,5,6,7,8,9>>},
+		  {"|slice:\"10:1:-1\"",
+		   <<"{{ var|slice:\"10:1:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<9,8,7,6,5,4,3>>},
+		  {"|slice:\"-111:-1:1\"",
+		   <<"{{ var|slice:\"-111:-1:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8>>},
+
+		  {"|slice:\"-111:-111:1\"",
+		   <<"{{ var|slice:\"-111:-111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"111:111:1\"",
+		   <<"{{ var|slice:\"111:111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"-111:111:1\"",
+		   <<"{{ var|slice:\"-111:111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<1,2,3,4,5,6,7,8,9>>},
+		  {"|slice:\"111:-111:1\"",
+		   <<"{{ var|slice:\"111:-111:1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
 
-                {"|stringformat:\"f\"",
-                     <<"{{ var|stringformat:\"f\" }}">>, [{var, "1"}],
-                    <<"1.000000">>},                    
-                {"|stringformat:\".2f\"",
-                     <<"{{ var|stringformat:\".2f\" }}">>, [{var, "1"}],
-                    <<"1.00">>},
-                {"|stringformat:\"0.2f\"",
-                     <<"{{ var|stringformat:\"0.2f\" }}">>, [{var, "1"}],
-                    <<"1.00">>},
-                {"|stringformat:\"-0.2f\"",
-                     <<"{{ var|stringformat:\"-0.2f\" }}">>, [{var, "1"}],
-                    <<"1.00">>},
-                {"|stringformat:\"10.2f\"",
-                     <<"{{ var|stringformat:\"10.2f\" }}">>, [{var, "1"}],
-                    <<"      1.00">>},
-                {"|stringformat:\"-10.2f\"",
-                     <<"{{ var|stringformat:\"-10.2f\" }}">>, [{var, "1"}],
-                    <<"1.00      ">>},                                                                                  
-                {"|stringformat:\".2f\"",
-                     <<"{{ var|stringformat:\".2f\" }}">>, [{var, "1"}],
-                    <<"1.00">>},                          
-                {"|stringformat:\"x\"",
-                     <<"{{ var|stringformat:\"x\" }}">>, [{var, "90"}],
-                    <<"5a">>},
-                {"|stringformat:\"X\"",
-                     <<"{{ var|stringformat:\"X\" }}">>, [{var, "90"}],
-                    <<"5A">>},
-        
-                {"|stringformat:\"o\"",
-                     <<"{{ var|stringformat:\"o\" }}">>, [{var, "90"}],
-                    <<"132">>}, 
-                                 
-                {"|stringformat:\"e\"",
-                     <<"{{ var|stringformat:\"e\" }}">>, [{var, "90"}],
-                    <<"9.000000e+01">>}, 
-                {"|stringformat:\"e\"",
-                     <<"{{ var|stringformat:\"e\" }}">>, [{var, "90000000000"}],
-                    <<"9.000000e+10">>},
-                {"|stringformat:\"E\"",
-                     <<"{{ var|stringformat:\"E\" }}">>, [{var, "90"}],
-                    <<"9.000000E+01">>},
-                {"|striptags",
-                     <<"{{ var|striptags }}">>, [{var, "<b>Joel</b> <button>is</button> a <span>slug</span>"}],
-                    <<"Joel is a slug">>},
-                {"|striptags",
-                     <<"{{ var|striptags }}">>, [{var, "<B>Joel</B> <button>is</button> a <span>slug</Span>"}],
-                    <<"Joel is a slug">>},
-                {"|striptags",
-                     <<"{{ var|striptags }}">>, [{var, "Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">http://www.djangoproject.com</a>"}],
-                    <<"Check out http://www.djangoproject.com">>},
-                {"|time:\"H:i\"",
-                     <<"{{ var|time:\"H:i\" }}">>, [{var, {{2010,12,1}, {10,11,12}} }],
-                    <<"10:11">>},
-                {"|time",
-                     <<"{{ var|time }}">>, [{var, {{2010,12,1}, {10,11,12}} }],
-                    <<"10:11 a.m.">>},
-               {"|timesince:from_date",
-                    <<"{{ from_date|timesince:conference_date }}">>, [{conference_date, {{2006,6,1},{8,0,0}} }, {from_date, {{2006,6,1},{0,0,0}} }],
+		  {"|slice:\"-111:-111:-1\"",
+		   <<"{{ var|slice:\"-111:-111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"111:111:-1\"",
+		   <<"{{ var|slice:\"111:111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"-111:111:-1\"",
+		   <<"{{ var|slice:\"-111:111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<>>},
+		  {"|slice:\"111:-111:-1\"",
+		   <<"{{ var|slice:\"111:-111:-1\" }}">>, [{var, [1,2,3,4,5,6,7,8,9]}],
+		   <<9,8,7,6,5,4,3,2,1>>},              {"|phone2numeric",
+							 <<"{{ var1|phone2numeric }}">>, [{var1, "1-800-COLLECT"}],
+							 <<"1-800-2655328">>},
+		  {"|slugify",
+		   <<"{{ var1|slugify }}">>, [{var1, "What The $#_! Was He Thinking?"}],
+		   <<"what-the-_-was-he-thinking">>},
+		  {"|slice:\"s\"",
+		   <<"{{ var|stringformat:\"s\" }}">>, [{var, "test"}],
+		   <<"test">>},
+		  {"|stringformat:\"s\"",
+		   <<"{{ var|stringformat:\"s\" }}">>, [{var, "test"}],
+		   <<"test">>},
+		  {"|stringformat:\"s\"",
+		   <<"{{ var|stringformat:\"s\" }}">>, [{var, "1"}],
+		   <<"1">>},
+		  {"|stringformat:\"s\"",
+		   <<"{{ var|stringformat:\"s\" }}">>, [{var, "test"}],
+		   <<"test">>},
+		  {"|stringformat:\"10s\"",
+		   <<"{{ var|stringformat:\"10s\" }}">>, [{var, "test"}],
+		   <<"      test">>},
+		  {"|stringformat:\"-10s\"",
+		   <<"{{ var|stringformat:\"-10s\" }}">>, [{var, "test"}],
+		   <<"test      ">>},
+
+		  {"|stringformat:\"d\"",
+		   <<"{{ var|stringformat:\"d\" }}">>, [{var, "90"}],
+		   <<"90">>},  
+		  {"|stringformat:\"10d\"",
+		   <<"{{ var|stringformat:\"10d\" }}">>, [{var, "90"}],
+		   <<"        90">>},
+		  {"|stringformat:\"-10d\"",
+		   <<"{{ var|stringformat:\"-10d\" }}">>, [{var, "90"}],
+		   <<"90        ">>},
+		  {"|stringformat:\"i\"",
+		   <<"{{ var|stringformat:\"i\" }}">>, [{var, "90"}],
+		   <<"90">>},  
+		  {"|stringformat:\"10i\"",
+		   <<"{{ var|stringformat:\"10i\" }}">>, [{var, "90"}],
+		   <<"        90">>},
+		  {"|stringformat:\"-10i\"",
+		   <<"{{ var|stringformat:\"-10i\" }}">>, [{var, "90"}],
+		   <<"90        ">>},
+		  {"|stringformat:\"0.2d\"",
+		   <<"{{ var|stringformat:\"0.2d\" }}">>, [{var, "9"}],
+		   <<"09">>},    
+		  {"|stringformat:\"10.4d\"",
+		   <<"{{ var|stringformat:\"10.4d\" }}">>, [{var, "9"}],
+		   <<"      0009">>},
+		  {"|stringformat:\"-10.4d\"",
+		   <<"{{ var|stringformat:\"-10.4d\" }}">>, [{var, "9"}],
+		   <<"0009      ">>},
+
+		  {"|stringformat:\"f\"",
+		   <<"{{ var|stringformat:\"f\" }}">>, [{var, "1"}],
+		   <<"1.000000">>},                    
+		  {"|stringformat:\".2f\"",
+		   <<"{{ var|stringformat:\".2f\" }}">>, [{var, "1"}],
+		   <<"1.00">>},
+		  {"|stringformat:\"0.2f\"",
+		   <<"{{ var|stringformat:\"0.2f\" }}">>, [{var, "1"}],
+		   <<"1.00">>},
+		  {"|stringformat:\"-0.2f\"",
+		   <<"{{ var|stringformat:\"-0.2f\" }}">>, [{var, "1"}],
+		   <<"1.00">>},
+		  {"|stringformat:\"10.2f\"",
+		   <<"{{ var|stringformat:\"10.2f\" }}">>, [{var, "1"}],
+		   <<"      1.00">>},
+		  {"|stringformat:\"-10.2f\"",
+		   <<"{{ var|stringformat:\"-10.2f\" }}">>, [{var, "1"}],
+		   <<"1.00      ">>},                                                                                  
+		  {"|stringformat:\".2f\"",
+		   <<"{{ var|stringformat:\".2f\" }}">>, [{var, "1"}],
+		   <<"1.00">>},                          
+		  {"|stringformat:\"x\"",
+		   <<"{{ var|stringformat:\"x\" }}">>, [{var, "90"}],
+		   <<"5a">>},
+		  {"|stringformat:\"X\"",
+		   <<"{{ var|stringformat:\"X\" }}">>, [{var, "90"}],
+		   <<"5A">>},
+
+		  {"|stringformat:\"o\"",
+		   <<"{{ var|stringformat:\"o\" }}">>, [{var, "90"}],
+		   <<"132">>}, 
+
+		  {"|stringformat:\"e\"",
+		   <<"{{ var|stringformat:\"e\" }}">>, [{var, "90"}],
+		   <<"9.000000e+01">>}, 
+		  {"|stringformat:\"e\"",
+		   <<"{{ var|stringformat:\"e\" }}">>, [{var, "90000000000"}],
+		   <<"9.000000e+10">>},
+		  {"|stringformat:\"E\"",
+		   <<"{{ var|stringformat:\"E\" }}">>, [{var, "90"}],
+		   <<"9.000000E+01">>},
+		  {"|striptags",
+		   <<"{{ var|striptags }}">>, [{var, "<b>Joel</b> <button>is</button> a <span>slug</span>"}],
+		   <<"Joel is a slug">>},
+		  {"|striptags",
+		   <<"{{ var|striptags }}">>, [{var, "<B>Joel</B> <button>is</button> a <span>slug</Span>"}],
+		   <<"Joel is a slug">>},
+		  {"|striptags",
+		   <<"{{ var|striptags }}">>, [{var, "Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">http://www.djangoproject.com</a>"}],
+		   <<"Check out http://www.djangoproject.com">>},
+		  {"|time:\"H:i\"",
+		   <<"{{ var|time:\"H:i\" }}">>, [{var, {{2010,12,1}, {10,11,12}} }],
+		   <<"10:11">>},
+		  {"|time",
+		   <<"{{ var|time }}">>, [{var, {{2010,12,1}, {10,11,12}} }],
+		   <<"10:11 a.m.">>},
+		  {"|timesince:from_date",
+		   <<"{{ from_date|timesince:conference_date }}">>, [{conference_date, {{2006,6,1},{8,0,0}} }, {from_date, {{2006,6,1},{0,0,0}} }],
                    <<"8 hours">>},
-                 {"|timesince:from_date",
-                      <<"{{ from_date|timesince:conference_date }}">>, [{conference_date, {{2010,6,1},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
-                     <<"4 years, 1 day">>}, % leap year
-                 {"|timesince:from_date",
-                      <<"{{ from_date|timesince:conference_date }}">>, [{conference_date, {{2006,7,15},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
-                     <<"1 month, 2 weeks">>},
-                 {"|timeuntil:from_date",
-                      <<"{{ conference_date|timeuntil:from_date }}">>, [{conference_date, {{2006,6,1},{8,0,0}} }, {from_date, {{2006,6,1},{0,0,0}} }],
-                     <<"8 hours">>},
-                 {"|timeuntil:from_date",
-                      <<"{{ conference_date|timeuntil:from_date }}">>, [{conference_date, {{2010,6,1},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
-                     <<"4 years, 1 day">>},
-                 {"|timeuntil:from_date",
-                      <<"{{ conference_date|timeuntil:from_date }}">>, [{conference_date, {{2006,7,15},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
-                     <<"1 month, 2 weeks">>},
-                {"|title",
-                    <<"{{ \"my title case\"|title }}">>, [],
-                    <<"My Title Case">>},
-                {"|title (pre-formatted)",
-                    <<"{{ \"My Title Case\"|title }}">>, [],
-                    <<"My Title Case">>},
-                {"|title (wacky separators)",
-                    <<"{{ \"my-title!case\"|title }}">>, [],
-                    <<"My-Title!Case">>},
-                {"|title (numbers)",
-                    <<"{{ \"my-title123CaSe\"|title }}">>, [],
-                    <<"My-Title123case">>},
-                {"|title (Irish names)",
-                    <<"{{ \"who's o'malley?\"|title }}">>, [],
-                    <<"Who's O'Malley?">>},
-                {"|truncatechars:0",
-                    <<"{{ var1|truncatechars:0 }}">>, [{var1, "Empty Me"}],
-                    <<"">>},
-                {"|truncatechars:11",
-                    <<"{{ var1|truncatechars:11 }}">>, [{var1, "Truncate Me Please"}],
-                    <<"Truncate Me...">>},
-                {"|truncatechars:17",
-                    <<"{{ var1|truncatechars:17 }}">>, [{var1, "Don't Truncate Me"}],
-                    <<"Don't Truncate Me">>},
-                {"|truncatechars:1 (UTF-8)",
-                    <<"{{ var1|truncatechars:1 }}">>, [{var1, "\x{E2}\x{82}\x{AC}1.99"}],
-                    <<"\x{E2}\x{82}\x{AC}...">>},
-                {"|truncatechars:2 (UTF-8)",
-                    <<"{{ var1|truncatechars:2 }}">>, [{var1, "\x{E2}\x{82}\x{AC}1.99"}],
-                    <<"\x{E2}\x{82}\x{AC}1...">>},
-                {"|truncatewords:0",
-                    <<"{{ var1|truncatewords:0 }}">>, [{var1, "Empty Me"}],
-                    <<"">>},
-                {"|truncatewords:2",
-                    <<"{{ var1|truncatewords:2 }}">>, [{var1, "Truncate Me Please"}],
-                    <<"Truncate Me...">>},
-                {"|truncatewords:3",
-                    <<"{{ var1|truncatewords:3 }}">>, [{var1, "Don't Truncate Me"}],
-                    <<"Don't Truncate Me">>},
-                {"|truncatewords_html:4",
-                    <<"{{ var1|truncatewords_html:4 }}">>, [{var1, "<p>The <strong>Long and <em>Winding</em> Road</strong> is too long</p>"}],
-                    <<"<p>The <strong>Long and <em>Winding</em>...</strong></p>">>},
-                {"|unordered_list",
-                    <<"{{ var1|unordered_list }}">>, [{var1, ["States", ["Kansas", ["Lawrence", "Topeka"], "Illinois"]]}],
-                    <<"<li>States<ul><li>Kansas<ul><li>Lawrence</li><li>Topeka</li></ul></li><li>Illinois</li></ul></li>">>},
-                {"|upper",
-                    <<"{{ message|upper }}">>, [{message, "That man has a gun."}],
-                    <<"THAT MAN HAS A GUN.">>},
-                {"|urlencode",
-                    <<"{{ url|urlencode }}">>, [{url, "You #$*@!!"}],
-                    <<"You+%23%24%2A%40%21%21">>},
-                {"|urlize",    
-                    <<"{{ var|urlize }}">>, [{var, "Check out www.djangoproject.com"}],
-                    <<"Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">www.djangoproject.com</a>">>},
-                {"|urlize",    
-                    <<"{{ var|urlize }}">>, [{var, "Check out http://www.djangoproject.com"}],
-                    <<"Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">http://www.djangoproject.com</a>">>},
-                {"|urlize",    
-                    <<"{{ var|urlize }}">>, [{var, "Check out \"http://www.djangoproject.com\""}],
-                    <<"Check out \"<a href=\"http://www.djangoproject.com\" rel=\"nofollow\">http://www.djangoproject.com</a>\"">>},
-                {"|urlizetrunc:15",    
-                    <<"{{ var|urlizetrunc:15 }}">>, [{var, "Check out www.djangoproject.com"}],
-                    <<"Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">www.djangopr...</a>">>},    
-                {"|wordcount",
-                    <<"{{ words|wordcount }}">>, [{words, "Why Hello There!"}],
-                    <<"3">>},
-                {"|wordwrap:2",
-                    <<"{{ words|wordwrap:2 }}">>, [{words, "this is"}],
-                    <<"this \nis">>},
-                {"|wordwrap:100",
-                    <<"{{ words|wordwrap:100 }}">>, [{words, "testing    testing"}],
-                    <<"testing    testing">>},
-                {"|wordwrap:10",
-                    <<"{{ words|wordwrap:10 }}">>, [{words, ""}],
-                    <<"">>},
-                {"|wordwrap:1",
-                    <<"{{ words|wordwrap:1 }}">>, [{words, "two"}],
-                    <<"two">>},
-               % yesno match: \?assert.*\( (.*), erlydtl_filters:(.*)\((.*), "(.*)"\)\)
-               % yesno replace: \t\t{"|$2:\"$4\"",\n\t\t\t\t\t <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],\n\t\t\t\t\t<<$1>>}
-                {"|yesno:\"yeah,no,maybe\"",
-                     <<"{{ var|yesno:\"yeah,no,maybe\" }}">>, [{var, true}],
-                    <<"yeah">>},
-                {"|yesno:\"yeah,no,maybe\"",
-                     <<"{{ var|yesno:\"yeah,no,maybe\" }}">>, [{var, false}],
-                    <<"no">>},
-                {"|yesno:\"yeah,no\"",
-                     <<"{{ var|yesno:\"yeah,no\" }}">>, [{var, undefined}],
-                    <<"no">>},
-                {"|yesno:\"yeah,no,maybe\"",
-                     <<"{{ var|yesno:\"yeah,no,maybe\" }}">>, [{var, undefined}],
-                    <<"maybe">>}
-            ]},
-        {"filters_if", [
-                {"Filter if 1.1",
-                    <<"{% if var1|length_is:0 %}Y{% else %}N{% endif %}">>,
-                     [{var1, []}],
-                     <<"Y">>},
-                {"Filter if 1.2",
-                    <<"{% if var1|length_is:1 %}Y{% else %}N{% endif %}">>,
-                     [{var1, []}],
-                     <<"N">>},
-                {"Filter if 1.3",
-                    <<"{% if var1|length_is:7 %}Y{% else %}N{% endif %}">>,
-                     [{var1, []}],
-                     <<"N">>},
-                {"Filter if 2.1",
-                    <<"{% if var1|length_is:0 %}Y{% else %}N{% endif %}">>,
-                     [{var1, ["foo"]}],
-                     <<"N">>},
-                {"Filter if 2.2",
-                    <<"{% if var1|length_is:1 %}Y{% else %}N{% endif %}">>,
-                     [{var1, ["foo"]}],
-                     <<"Y">>},
-                {"Filter if 2.3",
-                    <<"{% if var1|length_is:7 %}Y{% else %}N{% endif %}">>,
-                     [{var1, ["foo"]}],
-                     <<"N">>},
-                {"Filter if 3.1",
-                    <<"{% ifequal var1|length 0 %}Y{% else %}N{% endifequal %}">>,
-                     [{var1, []}],
-                     <<"Y">>},
-                {"Filter if 3.2",
-                    <<"{% ifequal var1|length 1 %}Y{% else %}N{% endifequal %}">>,
-                     [{var1, []}],
-                     <<"N">>},
-                {"Filter if 4.1",
-                    <<"{% ifequal var1|length 3 %}Y{% else %}N{% endifequal %}">>,
-                     [{var1, ["foo", "bar", "baz"]}],
-                     <<"Y">>},
-                {"Filter if 4.2",
-                    <<"{% ifequal var1|length 0 %}Y{% else %}N{% endifequal %}">>,
-                     [{var1, ["foo", "bar", "baz"]}],
-                     <<"N">>},
-                {"Filter if 4.3",
-                    <<"{% ifequal var1|length 1 %}Y{% else %}N{% endifequal %}">>,
-                     [{var1, ["foo", "bar", "baz"]}],
-                     <<"N">>}
-        ]},
-    {"firstof", [
-            {"Firstof first",
-                <<"{% firstof foo bar baz %}">>,
-                [{foo, "1"},{bar, "2"}],
-                <<"1">>},
-            {"Firstof second",
-                <<"{% firstof foo bar baz %}">>,
-                [{bar, "2"}],
-                <<"2">>},
-            {"Firstof none",
-                <<"{% firstof foo bar baz %}">>,
-                [],
-                <<"">>},
-            {"Firstof complex",
-                <<"{% firstof foo.bar.baz bar %}">>,
-                [{foo, [{bar, [{baz, "quux"}]}]}],
-                <<"quux">>},
-            {"Firstof undefined complex",
-                <<"{% firstof foo.bar.baz bar %}">>,
-                [{bar, "bar"}],
-                <<"bar">>},
-            {"Firstof literal",
-                <<"{% firstof foo bar \"baz\" %}">>,
-                [],
-                <<"baz">>}
-        ]},
-    {"regroup", [
-            {"Ordered", <<"{% regroup people by gender as gender_list %}{% for gender in gender_list %}{{ gender.grouper }}\n{% for item in gender.list %}{{ item.first_name }}\n{% endfor %}{% endfor %}{% endregroup %}">>, 
-                [{people, [[{first_name, "George"}, {gender, "Male"}], [{first_name, "Bill"}, {gender, "Male"}],
-                            [{first_name, "Margaret"}, {gender, "Female"}], [{first_name, "Condi"}, {gender, "Female"}]]}],
-                <<"Male\nGeorge\nBill\nFemale\nMargaret\nCondi\n">>},
-            {"Unordered", <<"{% regroup people by gender as gender_list %}{% for gender in gender_list %}{{ gender.grouper }}\n{% for item in gender.list %}{{ item.first_name }}\n{% endfor %}{% endfor %}{% endregroup %}">>, 
-                [{people, [[{first_name, "George"}, {gender, "Male"}], 
-                            [{first_name, "Margaret"}, {gender, "Female"}], 
-                            [{first_name, "Condi"}, {gender, "Female"}],
-                            [{first_name, "Bill"}, {gender, "Male"}]
-                        ]}],
-                <<"Male\nGeorge\nFemale\nMargaret\nCondi\nMale\nBill\n">>},
-	    {"NestedOrdered", <<"{% regroup people by name.last as lastname_list %}{% for lastname in lastname_list %}{{ lastname.grouper }}\n{% for item in lastname.list %}{{ item.name.first }}\n{% endfor %}{% endfor %}{% endregroup %}">>,
-                [{people, [[{name, [{first,"George"},{last,"Costanza"}]}],
-			   [{name, [{first,"Margaret"},{last,"Costanza"}]}],
-			   [{name, [{first,"Bill"},{last,"Buffalo"}]}],
-			   [{name, [{first,"Condi"},{last,"Buffalo"}]}]]}],
-               <<"Costanza\nGeorge\nMargaret\nBuffalo\nBill\nCondi\n">>},
-	    {"NestedUnordered", <<"{% regroup people by name.last as lastname_list %}{% for lastname in lastname_list %}{{ lastname.grouper }}\n{% for item in lastname.list %}{{ item.name.first }}\n{% endfor %}{% endfor %}{% endregroup %}">>,
-                [{people, [[{name, [{first,"George"},{last,"Costanza"}]}],
-			   [{name, [{first,"Bill"},{last,"Buffalo"}]}],
-			   [{name, [{first,"Margaret"},{last,"Costanza"}]}],
-			   [{name, [{first,"Condi"},{last,"Buffalo"}]}]]}],
-               <<"Costanza\nGeorge\nBuffalo\nBill\nCostanza\nMargaret\nBuffalo\nCondi\n">>},
-	    {"Filter", <<"{% regroup people|dictsort:\"name.last\" by name.last as lastname_list %}{% for lastname in lastname_list %}{{ lastname.grouper }}\n{% for item in lastname.list %}{{ item.name.first }}\n{% endfor %}{% endfor %}{% endregroup %}">>,
-		  [{people, [[{name, [{first,"George"},{last,"Costanza"}]}],
-			     [{name, [{first,"Bill"},{last,"Buffalo"}]}],
-			     [{name, [{first,"Margaret"},{last,"Costanza"}]}],
-			     [{name, [{first,"Condi"},{last,"Buffalo"}]}]]}],
-		  <<"Buffalo\nBill\nCondi\nCostanza\nGeorge\nMargaret\n">>}
-        ]},
-    {"spaceless", [
-            {"Beginning", <<"{% spaceless %}    <b>foo</b>{% endspaceless %}">>, [], <<"<b>foo</b>">>},
-            {"Middle", <<"{% spaceless %}<b>foo</b>  <b>bar</b>{% endspaceless %}">>, [], <<"<b>foo</b><b>bar</b>">>},
-            {"End", <<"{% spaceless %}<b>foo</b>  {% endspaceless %}">>, [], <<"<b>foo</b>">>},
-            {"NewLine", <<"{% spaceless %}\n<div> \n <b>foo</b> \n </div>\n {% endspaceless %}">>, [], <<"<div><b>foo</b></div>">>}
-        ]},
-    {"templatetag", [
-            {"openblock", <<"{% templatetag openblock %}">>, [], <<"{%">>},
-            {"closeblock", <<"{% templatetag closeblock %}">>, [], <<"%}">>},
-            {"openvariable", <<"{% templatetag openvariable %}">>, [], <<"{{">>},
-            {"closevariable", <<"{% templatetag closevariable %}">>, [], <<"}}">>},
-            {"openbrace", <<"{% templatetag openbrace %}">>, [], <<"{">>},
-            {"closebrace", <<"{% templatetag closebrace %}">>, [], <<"}">>},
-            {"opencomment", <<"{% templatetag opencomment %}">>, [], <<"{#">>},
-            {"closecomment", <<"{% templatetag closecomment %}">>, [], <<"#}">>}
-        ]},
-    {"trans",
-        [
-            {"trans functional default locale",
-                <<"Hello {% trans \"Hi\" %}">>, [], <<"Hello Hi">>
-            },
-            {"trans functional reverse locale",
-                <<"Hello {% trans \"Hi\" %}">>, [], [], [{locale, "reverse"}], <<"Hello iH">>
-            },
-            {"trans literal at run-time",
-                <<"Hello {% trans \"Hi\" %}">>, [], [{translation_fun, fun("Hi") -> "Konichiwa" end}], [],
-                <<"Hello Konichiwa">>},
-            {"trans variable at run-time",
-                <<"Hello {% trans var1 %}">>, [{var1, <<"Hi">>}], [{translation_fun, fun(<<"Hi">>) -> <<"Konichiwa">> end}], [],
-                <<"Hello Konichiwa">>},
-            {"trans literal at run-time: No-op",
-                <<"Hello {% trans \"Hi\" noop %}">>, [], [{translation_fun, fun("Hi") -> <<"Konichiwa">> end}], [],
-                <<"Hello Hi">>},
-            {"trans variable at run-time: No-op",
-                <<"Hello {% trans var1 noop %}">>, [{var1, <<"Hi">>}], [{translation_fun, fun(<<"Hi">>) -> <<"Konichiwa">> end}], [],
-                <<"Hello Hi">>}
-        ]},
-    {"blocktrans",
-        [
-            {"blocktrans default locale",
-                <<"{% blocktrans %}Hello{% endblocktrans %}">>, [], <<"Hello">>},
-            {"blocktrans choose locale",
-                <<"{% blocktrans %}Hello, {{ name }}{% endblocktrans %}">>, [{name, "Mr. President"}], [{locale, "de"}],
-                [{blocktrans_locales, ["de"]}, {blocktrans_fun, fun("Hello, {{ name }}", "de") -> <<"Guten tag, {{ name }}">> end}], <<"Guten tag, Mr. President">>},
-            {"blocktrans with args",
-                <<"{% blocktrans with var1=foo %}{{ var1 }}{% endblocktrans %}">>, [{foo, "Hello"}], <<"Hello">>}
-        ]},
-    {"verbatim", [
-            {"Plain verbatim",
-                <<"{% verbatim %}{{ oh no{% foobar %}{% endverbatim %}">>, [],
-                <<"{{ oh no{% foobar %}">>},
-            {"Named verbatim",
-                <<"{% verbatim foobar %}{% verbatim %}{% endverbatim foobar2 %}{% endverbatim foobar %}">>, [],
-                <<"{% verbatim %}{% endverbatim foobar2 %}">>}
-        ]},
-    {"widthratio", [
-            {"Literals", <<"{% widthratio 5 10 100 %}">>, [], <<"50">>},
-            {"Rounds up", <<"{% widthratio a b 100 %}">>, [{a, 175}, {b, 200}], <<"88">>}
-        ]},
-    {"with", [
-            {"Cache literal",
+		  {"|timesince:from_date",
+		   <<"{{ from_date|timesince:conference_date }}">>, [{conference_date, {{2010,6,1},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
+		   <<"4 years, 1 day">>}, % leap year
+		  {"|timesince:from_date",
+		   <<"{{ from_date|timesince:conference_date }}">>, [{conference_date, {{2006,7,15},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
+		   <<"1 month, 2 weeks">>},
+		  {"|timeuntil:from_date",
+		   <<"{{ conference_date|timeuntil:from_date }}">>, [{conference_date, {{2006,6,1},{8,0,0}} }, {from_date, {{2006,6,1},{0,0,0}} }],
+		   <<"8 hours">>},
+		  {"|timeuntil:from_date",
+		   <<"{{ conference_date|timeuntil:from_date }}">>, [{conference_date, {{2010,6,1},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
+		   <<"4 years, 1 day">>},
+		  {"|timeuntil:from_date",
+		   <<"{{ conference_date|timeuntil:from_date }}">>, [{conference_date, {{2006,7,15},{8,0,0}} },{from_date, {{2006,6,1},{0,0,0}} }],
+		   <<"1 month, 2 weeks">>},
+		  {"|title",
+		   <<"{{ \"my title case\"|title }}">>, [],
+		   <<"My Title Case">>},
+		  {"|title (pre-formatted)",
+		   <<"{{ \"My Title Case\"|title }}">>, [],
+		   <<"My Title Case">>},
+		  {"|title (wacky separators)",
+		   <<"{{ \"my-title!case\"|title }}">>, [],
+		   <<"My-Title!Case">>},
+		  {"|title (numbers)",
+		   <<"{{ \"my-title123CaSe\"|title }}">>, [],
+		   <<"My-Title123case">>},
+		  {"|title (Irish names)",
+		   <<"{{ \"who's o'malley?\"|title }}">>, [],
+		   <<"Who's O'Malley?">>},
+		  {"|truncatechars:0",
+		   <<"{{ var1|truncatechars:0 }}">>, [{var1, "Empty Me"}],
+		   <<"">>},
+		  {"|truncatechars:11",
+		   <<"{{ var1|truncatechars:11 }}">>, [{var1, "Truncate Me Please"}],
+		   <<"Truncate Me...">>},
+		  {"|truncatechars:17",
+		   <<"{{ var1|truncatechars:17 }}">>, [{var1, "Don't Truncate Me"}],
+		   <<"Don't Truncate Me">>},
+		  {"|truncatechars:1 (UTF-8)",
+		   <<"{{ var1|truncatechars:1 }}">>, [{var1, "\x{E2}\x{82}\x{AC}1.99"}],
+		   <<"\x{E2}\x{82}\x{AC}...">>},
+		  {"|truncatechars:2 (UTF-8)",
+		   <<"{{ var1|truncatechars:2 }}">>, [{var1, "\x{E2}\x{82}\x{AC}1.99"}],
+		   <<"\x{E2}\x{82}\x{AC}1...">>},
+		  {"|truncatewords:0",
+		   <<"{{ var1|truncatewords:0 }}">>, [{var1, "Empty Me"}],
+		   <<"">>},
+		  {"|truncatewords:2",
+		   <<"{{ var1|truncatewords:2 }}">>, [{var1, "Truncate Me Please"}],
+		   <<"Truncate Me...">>},
+		  {"|truncatewords:3",
+		   <<"{{ var1|truncatewords:3 }}">>, [{var1, "Don't Truncate Me"}],
+		   <<"Don't Truncate Me">>},
+		  {"|truncatewords_html:4",
+		   <<"{{ var1|truncatewords_html:4 }}">>, [{var1, "<p>The <strong>Long and <em>Winding</em> Road</strong> is too long</p>"}],
+		   <<"<p>The <strong>Long and <em>Winding</em>...</strong></p>">>},
+		  {"|unordered_list",
+		   <<"{{ var1|unordered_list }}">>, [{var1, ["States", ["Kansas", ["Lawrence", "Topeka"], "Illinois"]]}],
+		   <<"<li>States<ul><li>Kansas<ul><li>Lawrence</li><li>Topeka</li></ul></li><li>Illinois</li></ul></li>">>},
+		  {"|upper",
+		   <<"{{ message|upper }}">>, [{message, "That man has a gun."}],
+		   <<"THAT MAN HAS A GUN.">>},
+		  {"|urlencode",
+		   <<"{{ url|urlencode }}">>, [{url, "You #$*@!!"}],
+		   <<"You+%23%24%2A%40%21%21">>},
+		  {"|urlize",    
+		   <<"{{ var|urlize }}">>, [{var, "Check out www.djangoproject.com"}],
+		   <<"Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">www.djangoproject.com</a>">>},
+		  {"|urlize",    
+		   <<"{{ var|urlize }}">>, [{var, "Check out http://www.djangoproject.com"}],
+		   <<"Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">http://www.djangoproject.com</a>">>},
+		  {"|urlize",    
+		   <<"{{ var|urlize }}">>, [{var, "Check out \"http://www.djangoproject.com\""}],
+		   <<"Check out \"<a href=\"http://www.djangoproject.com\" rel=\"nofollow\">http://www.djangoproject.com</a>\"">>},
+		  {"|urlizetrunc:15",    
+		   <<"{{ var|urlizetrunc:15 }}">>, [{var, "Check out www.djangoproject.com"}],
+		   <<"Check out <a href=\"http://www.djangoproject.com\" rel=\"nofollow\">www.djangopr...</a>">>},    
+		  {"|wordcount",
+		   <<"{{ words|wordcount }}">>, [{words, "Why Hello There!"}],
+		   <<"3">>},
+		  {"|wordwrap:2",
+		   <<"{{ words|wordwrap:2 }}">>, [{words, "this is"}],
+		   <<"this \nis">>},
+		  {"|wordwrap:100",
+		   <<"{{ words|wordwrap:100 }}">>, [{words, "testing    testing"}],
+		   <<"testing    testing">>},
+		  {"|wordwrap:10",
+		   <<"{{ words|wordwrap:10 }}">>, [{words, ""}],
+		   <<"">>},
+		  {"|wordwrap:1",
+		   <<"{{ words|wordwrap:1 }}">>, [{words, "two"}],
+		   <<"two">>},
+						% yesno match: \?assert.*\( (.*), erlydtl_filters:(.*)\((.*), "(.*)"\)\)
+						% yesno replace: \t\t{"|$2:\"$4\"",\n\t\t\t\t\t <<"{{ var|$2:\"$4\" }}">>, [{var, $3}],\n\t\t\t\t\t<<$1>>}
+		  {"|yesno:\"yeah,no,maybe\"",
+		   <<"{{ var|yesno:\"yeah,no,maybe\" }}">>, [{var, true}],
+		   <<"yeah">>},
+		  {"|yesno:\"yeah,no,maybe\"",
+		   <<"{{ var|yesno:\"yeah,no,maybe\" }}">>, [{var, false}],
+		   <<"no">>},
+		  {"|yesno:\"yeah,no\"",
+		   <<"{{ var|yesno:\"yeah,no\" }}">>, [{var, undefined}],
+		   <<"no">>},
+		  {"|yesno:\"yeah,no,maybe\"",
+		   <<"{{ var|yesno:\"yeah,no,maybe\" }}">>, [{var, undefined}],
+		   <<"maybe">>}
+		 ]},
+     {"filters_if", [
+		     {"Filter if 1.1",
+		      <<"{% if var1|length_is:0 %}Y{% else %}N{% endif %}">>,
+		      [{var1, []}],
+		      <<"Y">>},
+		     {"Filter if 1.2",
+		      <<"{% if var1|length_is:1 %}Y{% else %}N{% endif %}">>,
+		      [{var1, []}],
+		      <<"N">>},
+		     {"Filter if 1.3",
+		      <<"{% if var1|length_is:7 %}Y{% else %}N{% endif %}">>,
+		      [{var1, []}],
+		      <<"N">>},
+		     {"Filter if 2.1",
+		      <<"{% if var1|length_is:0 %}Y{% else %}N{% endif %}">>,
+		      [{var1, ["foo"]}],
+		      <<"N">>},
+		     {"Filter if 2.2",
+		      <<"{% if var1|length_is:1 %}Y{% else %}N{% endif %}">>,
+		      [{var1, ["foo"]}],
+		      <<"Y">>},
+		     {"Filter if 2.3",
+		      <<"{% if var1|length_is:7 %}Y{% else %}N{% endif %}">>,
+		      [{var1, ["foo"]}],
+		      <<"N">>},
+		     {"Filter if 3.1",
+		      <<"{% ifequal var1|length 0 %}Y{% else %}N{% endifequal %}">>,
+		      [{var1, []}],
+		      <<"Y">>},
+		     {"Filter if 3.2",
+		      <<"{% ifequal var1|length 1 %}Y{% else %}N{% endifequal %}">>,
+		      [{var1, []}],
+		      <<"N">>},
+		     {"Filter if 4.1",
+		      <<"{% ifequal var1|length 3 %}Y{% else %}N{% endifequal %}">>,
+		      [{var1, ["foo", "bar", "baz"]}],
+		      <<"Y">>},
+		     {"Filter if 4.2",
+		      <<"{% ifequal var1|length 0 %}Y{% else %}N{% endifequal %}">>,
+		      [{var1, ["foo", "bar", "baz"]}],
+		      <<"N">>},
+		     {"Filter if 4.3",
+		      <<"{% ifequal var1|length 1 %}Y{% else %}N{% endifequal %}">>,
+		      [{var1, ["foo", "bar", "baz"]}],
+		      <<"N">>}
+		    ]},
+     {"firstof", [
+		  {"Firstof first",
+		   <<"{% firstof foo bar baz %}">>,
+		   [{foo, "1"},{bar, "2"}],
+		   <<"1">>},
+		  {"Firstof second",
+		   <<"{% firstof foo bar baz %}">>,
+		   [{bar, "2"}],
+		   <<"2">>},
+		  {"Firstof none",
+		   <<"{% firstof foo bar baz %}">>,
+		   [],
+		   <<"">>},
+		  {"Firstof complex",
+		   <<"{% firstof foo.bar.baz bar %}">>,
+		   [{foo, [{bar, [{baz, "quux"}]}]}],
+		   <<"quux">>},
+		  {"Firstof undefined complex",
+		   <<"{% firstof foo.bar.baz bar %}">>,
+		   [{bar, "bar"}],
+		   <<"bar">>},
+		  {"Firstof literal",
+		   <<"{% firstof foo bar \"baz\" %}">>,
+		   [],
+		   <<"baz">>}
+		 ]},
+     {"regroup", [
+		  {"Ordered", <<"{% regroup people by gender as gender_list %}{% for gender in gender_list %}{{ gender.grouper }}\n{% for item in gender.list %}{{ item.first_name }}\n{% endfor %}{% endfor %}{% endregroup %}">>, 
+		   [{people, [[{first_name, "George"}, {gender, "Male"}], [{first_name, "Bill"}, {gender, "Male"}],
+			      [{first_name, "Margaret"}, {gender, "Female"}], [{first_name, "Condi"}, {gender, "Female"}]]}],
+		   <<"Male\nGeorge\nBill\nFemale\nMargaret\nCondi\n">>},
+		  {"Unordered", <<"{% regroup people by gender as gender_list %}{% for gender in gender_list %}{{ gender.grouper }}\n{% for item in gender.list %}{{ item.first_name }}\n{% endfor %}{% endfor %}{% endregroup %}">>, 
+		   [{people, [[{first_name, "George"}, {gender, "Male"}], 
+			      [{first_name, "Margaret"}, {gender, "Female"}], 
+			      [{first_name, "Condi"}, {gender, "Female"}],
+			      [{first_name, "Bill"}, {gender, "Male"}]
+			     ]}],
+		   <<"Male\nGeorge\nFemale\nMargaret\nCondi\nMale\nBill\n">>},
+		  {"NestedOrdered", <<"{% regroup people by name.last as lastname_list %}{% for lastname in lastname_list %}{{ lastname.grouper }}\n{% for item in lastname.list %}{{ item.name.first }}\n{% endfor %}{% endfor %}{% endregroup %}">>,
+		   [{people, [[{name, [{first,"George"},{last,"Costanza"}]}],
+			      [{name, [{first,"Margaret"},{last,"Costanza"}]}],
+			      [{name, [{first,"Bill"},{last,"Buffalo"}]}],
+			      [{name, [{first,"Condi"},{last,"Buffalo"}]}]]}],
+		   <<"Costanza\nGeorge\nMargaret\nBuffalo\nBill\nCondi\n">>},
+		  {"NestedUnordered", <<"{% regroup people by name.last as lastname_list %}{% for lastname in lastname_list %}{{ lastname.grouper }}\n{% for item in lastname.list %}{{ item.name.first }}\n{% endfor %}{% endfor %}{% endregroup %}">>,
+		   [{people, [[{name, [{first,"George"},{last,"Costanza"}]}],
+			      [{name, [{first,"Bill"},{last,"Buffalo"}]}],
+			      [{name, [{first,"Margaret"},{last,"Costanza"}]}],
+			      [{name, [{first,"Condi"},{last,"Buffalo"}]}]]}],
+		   <<"Costanza\nGeorge\nBuffalo\nBill\nCostanza\nMargaret\nBuffalo\nCondi\n">>},
+		  {"Filter", <<"{% regroup people|dictsort:\"name.last\" by name.last as lastname_list %}{% for lastname in lastname_list %}{{ lastname.grouper }}\n{% for item in lastname.list %}{{ item.name.first }}\n{% endfor %}{% endfor %}{% endregroup %}">>,
+		   [{people, [[{name, [{first,"George"},{last,"Costanza"}]}],
+			      [{name, [{first,"Bill"},{last,"Buffalo"}]}],
+			      [{name, [{first,"Margaret"},{last,"Costanza"}]}],
+			      [{name, [{first,"Condi"},{last,"Buffalo"}]}]]}],
+		   <<"Buffalo\nBill\nCondi\nCostanza\nGeorge\nMargaret\n">>}
+		 ]},
+     {"spaceless", [
+		    {"Beginning", <<"{% spaceless %}    <b>foo</b>{% endspaceless %}">>, [], <<"<b>foo</b>">>},
+		    {"Middle", <<"{% spaceless %}<b>foo</b>  <b>bar</b>{% endspaceless %}">>, [], <<"<b>foo</b><b>bar</b>">>},
+		    {"End", <<"{% spaceless %}<b>foo</b>  {% endspaceless %}">>, [], <<"<b>foo</b>">>},
+		    {"NewLine", <<"{% spaceless %}\n<div> \n <b>foo</b> \n </div>\n {% endspaceless %}">>, [], <<"<div><b>foo</b></div>">>}
+		   ]},
+     {"templatetag", [
+		      {"openblock", <<"{% templatetag openblock %}">>, [], <<"{%">>},
+		      {"closeblock", <<"{% templatetag closeblock %}">>, [], <<"%}">>},
+		      {"openvariable", <<"{% templatetag openvariable %}">>, [], <<"{{">>},
+		      {"closevariable", <<"{% templatetag closevariable %}">>, [], <<"}}">>},
+		      {"openbrace", <<"{% templatetag openbrace %}">>, [], <<"{">>},
+		      {"closebrace", <<"{% templatetag closebrace %}">>, [], <<"}">>},
+		      {"opencomment", <<"{% templatetag opencomment %}">>, [], <<"{#">>},
+		      {"closecomment", <<"{% templatetag closecomment %}">>, [], <<"#}">>}
+		     ]},
+     {"trans",
+      [
+       {"trans functional default locale",
+	<<"Hello {% trans \"Hi\" %}">>, [], <<"Hello Hi">>
+       },
+       {"trans functional reverse locale",
+	<<"Hello {% trans \"Hi\" %}">>, [], [], [{locale, "reverse"}], <<"Hello iH">>
+       },
+       {"trans literal at run-time",
+	<<"Hello {% trans \"Hi\" %}">>, [], [{translation_fun, fun("Hi") -> "Konichiwa" end}], [],
+	<<"Hello Konichiwa">>},
+       {"trans variable at run-time",
+	<<"Hello {% trans var1 %}">>, [{var1, <<"Hi">>}], [{translation_fun, fun(<<"Hi">>) -> <<"Konichiwa">> end}], [],
+	<<"Hello Konichiwa">>},
+       {"trans literal at run-time: No-op",
+	<<"Hello {% trans \"Hi\" noop %}">>, [], [{translation_fun, fun("Hi") -> <<"Konichiwa">> end}], [],
+	<<"Hello Hi">>},
+       {"trans variable at run-time: No-op",
+	<<"Hello {% trans var1 noop %}">>, [{var1, <<"Hi">>}], [{translation_fun, fun(<<"Hi">>) -> <<"Konichiwa">> end}], [],
+	<<"Hello Hi">>}
+      ]},
+     {"blocktrans",
+      [
+       {"blocktrans default locale",
+	<<"{% blocktrans %}Hello{% endblocktrans %}">>, [], <<"Hello">>},
+       {"blocktrans choose locale",
+	<<"{% blocktrans %}Hello, {{ name }}{% endblocktrans %}">>, [{name, "Mr. President"}], [{locale, "de"}],
+	[{blocktrans_locales, ["de"]}, {blocktrans_fun, fun("Hello, {{ name }}", "de") -> <<"Guten tag, {{ name }}">> end}], <<"Guten tag, Mr. President">>},
+       {"blocktrans with args",
+	<<"{% blocktrans with var1=foo %}{{ var1 }}{% endblocktrans %}">>, [{foo, "Hello"}], <<"Hello">>}
+      ]},
+     {"verbatim", [
+		   {"Plain verbatim",
+		    <<"{% verbatim %}{{ oh no{% foobar %}{% endverbatim %}">>, [],
+		    <<"{{ oh no{% foobar %}">>},
+		   {"Named verbatim",
+		    <<"{% verbatim foobar %}{% verbatim %}{% endverbatim foobar2 %}{% endverbatim foobar %}">>, [],
+		    <<"{% verbatim %}{% endverbatim foobar2 %}">>}
+		  ]},
+     {"widthratio", [
+		     {"Literals", <<"{% widthratio 5 10 100 %}">>, [], <<"50">>},
+		     {"Rounds up", <<"{% widthratio a b 100 %}">>, [{a, 175}, {b, 200}], <<"88">>}
+		    ]},
+     {"with", [
+	       {"Cache literal",
                 <<"{% with a=1 %}{{ a }}{% endwith %}">>, [], <<"1">>},
-            {"Cache variable",
+	       {"Cache variable",
                 <<"{% with a=b %}{{ a }}{% endwith %}">>, [{b, "foo"}], <<"foo">>},
-	      {"Cache variable with attribute",
-                    <<"I enjoy {% with a = var1 %}{{ a.game }}{% endwith %}">>, [{var1, [{game, "Othello"}]}], <<"I enjoy Othello">>},
-	      {"Cache variable attribute",
-                    <<"I enjoy {% with a = var1.game %}{{ a }}{% endwith %}">>, [{var1, [{game, "Othello"}]}], <<"I enjoy Othello">>},
-            {"Cache multiple",
+	       {"Cache variable with attribute",
+		<<"I enjoy {% with a = var1 %}{{ a.game }}{% endwith %}">>, [{var1, [{game, "Othello"}]}], <<"I enjoy Othello">>},
+	       {"Cache variable attribute",
+		<<"I enjoy {% with a = var1.game %}{{ a }}{% endwith %}">>, [{var1, [{game, "Othello"}]}], <<"I enjoy Othello">>},
+	       {"Cache multiple",
                 <<"{% with alpha=1 beta=b %}{{ alpha }}/{{ beta }}{% endwith %}">>, [{b, 2}], <<"1/2">>}
-        ]},
+	      ]},
      {"unicode", [
-             {"(tm) somewhere",
-                 <<"™">>, [], <<"™">>}
-        ]},
+		  {"(tm) somewhere",
+		   <<"™">>, [], <<"™">>}
+		 ]},
      {"contrib_humanize", [
-             {"intcomma",
-                 <<"{{ a|intcomma }} {{ b|intcomma }} {{ c|intcomma }} {{ d|intcomma }}">>,
-                     [{a, 999}, {b, 123456789}, {c, 12345}, {d, 1234567890}],
-                     <<"999 123,456,789 12,345 1,234,567,890">>}
-        ]}
+			   {"intcomma",
+			    <<"{{ a|intcomma }} {{ b|intcomma }} {{ c|intcomma }} {{ d|intcomma }}">>,
+			    [{a, 999}, {b, 123456789}, {c, 12345}, {d, 1234567890}],
+			    <<"999 123,456,789 12,345 1,234,567,890">>}
+			  ]},
+     %% custom syntax stuff
+     {"extension_module", [
+			   %% the erlydtl_extension_test module replaces a foo identifier with bar when hitting a # following foo.
+			   {"replace parsed token", <<"{{ foo # }}">>, [{bar, "ok"}], [], [{extension_module, erlydtl_extension_test}], <<"ok">>},
+			   {"proper error message", <<"{{ bar # }}">>, [{bar, "ok"}], [], [{extension_module, erlydtl_extension_test}],
+			    {error, {1,erlydtl_extension_test,"Unexpected '#' in code at column 8"}}},
+                           %% accept identifiers as expressions (this is a dummy functionality to test the parser extensibility)
+			   {"identifiers as expressions", <<"{{ foo.bar or baz }}">>, [{baz, "ok"}], [], [{extension_module, erlydtl_extension_test}], <<"ok">>}
+			  ]}
     ].
- 
+
 run_tests() ->
     io:format("Running unit tests...~n"),
     DefaultOptions = [{custom_filters_modules, [erlydtl_contrib_humanize]}],
     Failures = lists:foldl(
-        fun({Group, Assertions}, GroupAcc) ->
-                io:format(" Test group ~p...~n", [Group]),
-                lists:foldl(fun
-                        ({Name, DTL, Vars, Output}, Acc) ->
-                            process_unit_test(erlydtl:compile(DTL, erlydtl_running_test, DefaultOptions),
-                                Vars, [], Output, Acc, Group, Name);
-                        ({Name, DTL, Vars, RenderOpts, Output}, Acc) ->
-                            process_unit_test(erlydtl:compile(DTL, erlydtl_running_test, DefaultOptions),
-                                Vars, RenderOpts, Output, Acc, Group, Name);
-                        ({Name, DTL, Vars, RenderOpts, CompilerOpts, Output}, Acc) ->
-                            process_unit_test(erlydtl:compile(DTL, erlydtl_running_test, CompilerOpts ++ DefaultOptions),
-                                Vars, RenderOpts, Output, Acc, Group, Name)
-                            end, GroupAcc, Assertions)
-        end, [], tests()),
- 
+		 fun({Group, Assertions}, GroupAcc) ->
+			 io:format(" Test group ~p...~n", [Group]),
+			 lists:foldl(fun
+					 ({Name, DTL, Vars, Output}, Acc) ->
+					    process_unit_test(erlydtl:compile(DTL, erlydtl_running_test, DefaultOptions),
+							      Vars, [], Output, Acc, Group, Name);
+					 ({Name, DTL, Vars, RenderOpts, Output}, Acc) ->
+					    process_unit_test(erlydtl:compile(DTL, erlydtl_running_test, DefaultOptions),
+							      Vars, RenderOpts, Output, Acc, Group, Name);
+					 ({Name, DTL, Vars, RenderOpts, CompilerOpts, Output}, Acc) ->
+					    process_unit_test(erlydtl:compile(DTL, erlydtl_running_test, CompilerOpts ++ DefaultOptions),
+							      Vars, RenderOpts, Output, Acc, Group, Name)
+				    end, GroupAcc, Assertions)
+		 end, [], tests()),
+
     io:format("Unit test failures: ~p~n", [lists:reverse(Failures)]).
- 
+
 process_unit_test(CompiledTemplate, Vars, RenderOpts, Output,Acc, Group, Name) ->
-        case CompiledTemplate of
-             {ok, _} ->
-                   {ok, IOList} = erlydtl_running_test:render(Vars, RenderOpts),
-                   {ok, IOListBin} = erlydtl_running_test:render(vars_to_binary(Vars), RenderOpts),
-                   case {iolist_to_binary(IOList), iolist_to_binary(IOListBin)} of
-                        {Output, Output} ->
-                                  Acc;
-                        {Output, Unexpected} ->
-                                  [{Group, Name, 'binary', Unexpected, Output} | Acc];
-                        {Unexpected, Output} ->
-                                  [{Group, Name, 'list', Unexpected, Output} | Acc];
-                        {Unexpected1, Unexpected2} ->
-                                  [{Group, Name, 'list', Unexpected1, Output},
-                                      {Group, Name, 'binary', Unexpected2, Output} | Acc]
-                   end;
-             Err ->
-                   [{Group, Name, Err} | Acc]
-        end.
- 
- 
+    case CompiledTemplate of
+	{ok, _} ->
+	    {ok, IOList} = erlydtl_running_test:render(Vars, RenderOpts),
+	    {ok, IOListBin} = erlydtl_running_test:render(vars_to_binary(Vars), RenderOpts),
+	    case {iolist_to_binary(IOList), iolist_to_binary(IOListBin)} of
+		{Output, Output} ->
+		    Acc;
+		{Output, Unexpected} ->
+		    [{Group, Name, 'binary', Unexpected, Output} | Acc];
+		{Unexpected, Output} ->
+		    [{Group, Name, 'list', Unexpected, Output} | Acc];
+		{Unexpected1, Unexpected2} ->
+		    [{Group, Name, 'list', Unexpected1, Output},
+		     {Group, Name, 'binary', Unexpected2, Output} | Acc]
+	    end;
+	Output -> Acc;
+	Err ->
+	    [{Group, Name, Err} | Acc]
+    end.
+
+
 vars_to_binary(Vars) when is_list(Vars) ->
     lists:map(fun
-            ({Key, [H|_] = Value}) when is_tuple(H) ->
-                {Key, vars_to_binary(Value)};
-            ({Key, [H|_] = Value}) when is_integer(H) ->
-                {Key, list_to_binary(Value)};
-            ({Key, Value}) ->
-                {Key, Value}
-        end, Vars);
+		  ({Key, [H|_] = Value}) when is_tuple(H) ->
+		     {Key, vars_to_binary(Value)};
+		  ({Key, [H|_] = Value}) when is_integer(H) ->
+		     {Key, list_to_binary(Value)};
+		  ({Key, Value}) ->
+		     {Key, Value}
+	     end, Vars);
 vars_to_binary(Vars) ->
     Vars.
- 
+
 generate_test_date() ->
     {{Y,M,D}, _} = erlang:localtime(),
     MonthName = [
-       "January", "February", "March", "April",
-       "May", "June", "July", "August", "September",
-       "October", "November", "December"
-    ],
+		 "January", "February", "March", "April",
+		 "May", "June", "July", "August", "September",
+		 "October", "November", "December"
+		],
     OrdinalSuffix = [
-       "st","nd","rd","th","th","th","th","th","th","th", % 1-10
-       "th","th","th","th","th","th","th","th","th","th", % 10-20
-       "st","nd","rd","th","th","th","th","th","th","th", % 20-30
-       "st"
-    ],
+		     "st","nd","rd","th","th","th","th","th","th","th", % 1-10
+		     "th","th","th","th","th","th","th","th","th","th", % 10-20
+		     "st","nd","rd","th","th","th","th","th","th","th", % 20-30
+		     "st"
+		    ],
     list_to_binary([
-         "It is the ",
-         integer_to_list(D),
-         lists:nth(D, OrdinalSuffix),
-         " of ", lists:nth(M, MonthName),
-         " ", integer_to_list(Y), "."
-    ]).
+		    "It is the ",
+		    integer_to_list(D),
+		    lists:nth(D, OrdinalSuffix),
+		    " of ", lists:nth(M, MonthName),
+		    " ", integer_to_list(Y), "."
+		   ]).