xref: /freebsd/contrib/ntp/sntp/ag-tpl/0-old/Mdoc.pm (revision 416ba5c74546f32a993436a99516d35008e9f384)
1*2b15cb3dSCy Schubert=head1 NAME
2*2b15cb3dSCy Schubert
3*2b15cb3dSCy SchubertMdoc - perl module to parse Mdoc macros
4*2b15cb3dSCy Schubert
5*2b15cb3dSCy Schubert=head1 SYNOPSIS
6*2b15cb3dSCy Schubert
7*2b15cb3dSCy Schubert    use Mdoc qw(ns pp soff son stoggle mapwords);
8*2b15cb3dSCy Schubert
9*2b15cb3dSCy SchubertSee mdoc2man and mdoc2texi for code examples.
10*2b15cb3dSCy Schubert
11*2b15cb3dSCy Schubert=head1 FUNCTIONS
12*2b15cb3dSCy Schubert
13*2b15cb3dSCy Schubert=over 4
14*2b15cb3dSCy Schubert
15*2b15cb3dSCy Schubert=item def_macro( NAME, CODE, [ raw => 1, greedy => 1, concat_until => '.Xx' ] )
16*2b15cb3dSCy Schubert
17*2b15cb3dSCy SchubertDefine new macro. The CODE reference will be called by call_macro(). You can
18*2b15cb3dSCy Schuberthave two distinct definitions for and inline macro and for a standalone macro
19*2b15cb3dSCy Schubert(i. e. 'Pa' and '.Pa').
20*2b15cb3dSCy Schubert
21*2b15cb3dSCy SchubertThe CODE reference is passed a list of arguments and is expected to return list
22*2b15cb3dSCy Schubertof strings and control characters (see C<CONSTANTS>).
23*2b15cb3dSCy Schubert
24*2b15cb3dSCy SchubertBy default the surrouding "" from arguments to macros are removed, use C<raw>
25*2b15cb3dSCy Schubertto disable this.
26*2b15cb3dSCy Schubert
27*2b15cb3dSCy SchubertNormaly CODE reference is passed all arguments up to next nested macro. Set
28*2b15cb3dSCy SchubertC<greedy> to to pass everything up to the end of the line.
29*2b15cb3dSCy Schubert
30*2b15cb3dSCy SchubertIf the concat_until is present, the line is concated until the .Xx macro is
31*2b15cb3dSCy Schubertfound. For example the following macro definition
32*2b15cb3dSCy Schubert
33*2b15cb3dSCy Schubert    def_macro('.Oo', gen_encloser(qw([ ]), concat_until => '.Oc' }
34*2b15cb3dSCy Schubert    def_macro('.Cm', sub { mapwords {'($_)'} @_ } }
35*2b15cb3dSCy Schubert
36*2b15cb3dSCy Schubertand the following input
37*2b15cb3dSCy Schubert
38*2b15cb3dSCy Schubert    .Oo
39*2b15cb3dSCy Schubert    .Cm foo |
40*2b15cb3dSCy Schubert    .Cm bar |
41*2b15cb3dSCy Schubert    .Oc
42*2b15cb3dSCy Schubert
43*2b15cb3dSCy Schubertresults in [(foo) | (bar)]
44*2b15cb3dSCy Schubert
45*2b15cb3dSCy Schubert=item get_macro( NAME )
46*2b15cb3dSCy Schubert
47*2b15cb3dSCy SchubertReturns a hash reference like:
48*2b15cb3dSCy Schubert
49*2b15cb3dSCy Schubert    { run => CODE, raw => [1|0], greedy => [1|0] }
50*2b15cb3dSCy Schubert
51*2b15cb3dSCy SchubertWhere C<CODE> is the CODE reference used to define macro called C<NAME>
52*2b15cb3dSCy Schubert
53*2b15cb3dSCy Schubert=item parse_line( INPUT, OUTPUT_CODE, PREPROCESS_CODE )
54*2b15cb3dSCy Schubert
55*2b15cb3dSCy SchubertParse a line from the C<INPUT> filehandle. If a macro was detected it returns a
56*2b15cb3dSCy Schubertlist (MACRO_NAME, @MACRO_ARGS), otherwise it calls the C<OUTPUT_CODE>, giving
57*2b15cb3dSCy Schubertcaller a chance to modify line before printing it. If C<PREPROCESS_CODE> is
58*2b15cb3dSCy Schubertdefined it calls it prior to passing argument to a macro, giving caller a
59*2b15cb3dSCy Schubertchance to alter them.  if EOF was reached undef is returned.
60*2b15cb3dSCy Schubert
61*2b15cb3dSCy Schubert=item call_macro( MACRO, ARGS, ... )
62*2b15cb3dSCy Schubert
63*2b15cb3dSCy SchubertCall macro C<MACRO> with C<ARGS>. The CODE reference for macro C<MACRO> is
64*2b15cb3dSCy Schubertcalled and for all the nested macros. Every called macro returns a list which
65*2b15cb3dSCy Schubertis appended to return value and returned when all nested macros are processed.
66*2b15cb3dSCy SchubertUse to_string() to produce a printable string from the list.
67*2b15cb3dSCy Schubert
68*2b15cb3dSCy Schubert=item to_string ( LIST )
69*2b15cb3dSCy Schubert
70*2b15cb3dSCy SchubertProcesses C<LIST> returned from call_macro() and returns formatted string.
71*2b15cb3dSCy Schubert
72*2b15cb3dSCy Schubert=item mapwords BLOCK ARRAY
73*2b15cb3dSCy Schubert
74*2b15cb3dSCy SchubertThis is like perl's map only it calls BLOCK only on elements which are not
75*2b15cb3dSCy Schubertpunctuation or control characters.
76*2b15cb3dSCy Schubert
77*2b15cb3dSCy Schubert=item space ( ['on'|'off] )
78*2b15cb3dSCy Schubert
79*2b15cb3dSCy SchubertTurn spacing on or off. If called without argument it returns the current state.
80*2b15cb3dSCy Schubert
81*2b15cb3dSCy Schubert=item gen_encloser ( START, END )
82*2b15cb3dSCy Schubert
83*2b15cb3dSCy SchubertHelper function for generating macros that enclose their arguments.
84*2b15cb3dSCy Schubert    gen_encloser(qw({ }));
85*2b15cb3dSCy Schubertreturns
86*2b15cb3dSCy Schubert    sub { '{', ns, @_, ns, pp('}')}
87*2b15cb3dSCy Schubert
88*2b15cb3dSCy Schubert=item set_Bl_callback( CODE , DEFS )
89*2b15cb3dSCy Schubert
90*2b15cb3dSCy SchubertThis module implements the Bl/El macros for you. Using set_Bl_callback you can
91*2b15cb3dSCy Schubertprovide a macro definition that should be executed on a .Bl call.
92*2b15cb3dSCy Schubert
93*2b15cb3dSCy Schubert=item set_El_callback( CODE , DEFS )
94*2b15cb3dSCy Schubert
95*2b15cb3dSCy SchubertThis module implements the Bl/El macros for you. Using set_El_callback you can
96*2b15cb3dSCy Schubertprovide a macro definition that should be executed on a .El call.
97*2b15cb3dSCy Schubert
98*2b15cb3dSCy Schubert=item set_Re_callback( CODE )
99*2b15cb3dSCy Schubert
100*2b15cb3dSCy SchubertThe C<CODE> is called after a Rs/Re block is done. With a hash reference as a
101*2b15cb3dSCy Schubertparameter, describing the reference.
102*2b15cb3dSCy Schubert
103*2b15cb3dSCy Schubert=back
104*2b15cb3dSCy Schubert
105*2b15cb3dSCy Schubert=head1 CONSTANTS
106*2b15cb3dSCy Schubert
107*2b15cb3dSCy Schubert=over 4
108*2b15cb3dSCy Schubert
109*2b15cb3dSCy Schubert=item ns
110*2b15cb3dSCy Schubert
111*2b15cb3dSCy SchubertIndicate 'no space' between to members of the list.
112*2b15cb3dSCy Schubert
113*2b15cb3dSCy Schubert=item pp ( STRING )
114*2b15cb3dSCy Schubert
115*2b15cb3dSCy SchubertThe string is 'punctuation point'. It means that every punctuation
116*2b15cb3dSCy Schubertpreceeding that element is put behind it.
117*2b15cb3dSCy Schubert
118*2b15cb3dSCy Schubert=item soff
119*2b15cb3dSCy Schubert
120*2b15cb3dSCy SchubertTurn spacing off.
121*2b15cb3dSCy Schubert
122*2b15cb3dSCy Schubert=item son
123*2b15cb3dSCy Schubert
124*2b15cb3dSCy SchubertTurn spacing on.
125*2b15cb3dSCy Schubert
126*2b15cb3dSCy Schubert=item stoggle
127*2b15cb3dSCy Schubert
128*2b15cb3dSCy SchubertToogle spacing.
129*2b15cb3dSCy Schubert
130*2b15cb3dSCy Schubert=item hs
131*2b15cb3dSCy Schubert
132*2b15cb3dSCy SchubertPrint space no matter spacing mode.
133*2b15cb3dSCy Schubert
134*2b15cb3dSCy Schubert=back
135*2b15cb3dSCy Schubert
136*2b15cb3dSCy Schubert=head1 TODO
137*2b15cb3dSCy Schubert
138*2b15cb3dSCy Schubert* The concat_until only works with standalone macros. This means that
139*2b15cb3dSCy Schubert    .Po blah Pc
140*2b15cb3dSCy Schubertwill hang until .Pc in encountered.
141*2b15cb3dSCy Schubert
142*2b15cb3dSCy Schubert* Provide default macros for Bd/Ed
143*2b15cb3dSCy Schubert
144*2b15cb3dSCy Schubert* The reference implementation is uncomplete
145*2b15cb3dSCy Schubert
146*2b15cb3dSCy Schubert=cut
147*2b15cb3dSCy Schubert
148*2b15cb3dSCy Schubertpackage Mdoc;
149*2b15cb3dSCy Schubertuse strict;
150*2b15cb3dSCy Schubertuse warnings;
151*2b15cb3dSCy Schubertuse List::Util qw(reduce);
152*2b15cb3dSCy Schubertuse Text::ParseWords qw(quotewords);
153*2b15cb3dSCy Schubertuse Carp;
154*2b15cb3dSCy Schubertuse Exporter qw(import);
155*2b15cb3dSCy Schubertour @EXPORT_OK = qw(ns pp soff son stoggle hs mapwords gen_encloser nl);
156*2b15cb3dSCy Schubert
157*2b15cb3dSCy Schubertuse constant {
158*2b15cb3dSCy Schubert    ns      => ['nospace'],
159*2b15cb3dSCy Schubert    soff    => ['spaceoff'],
160*2b15cb3dSCy Schubert    son     => ['spaceon'],
161*2b15cb3dSCy Schubert    stoggle => ['spacetoggle'],
162*2b15cb3dSCy Schubert    hs      => ['hardspace'],
163*2b15cb3dSCy Schubert};
164*2b15cb3dSCy Schubert
165*2b15cb3dSCy Schubertsub pp {
166*2b15cb3dSCy Schubert    my $c = shift;
167*2b15cb3dSCy Schubert    return ['pp', $c ];
168*2b15cb3dSCy Schubert}
169*2b15cb3dSCy Schubertsub gen_encloser {
170*2b15cb3dSCy Schubert    my ($o, $c) = @_;
171*2b15cb3dSCy Schubert    return sub { ($o, ns, @_, ns, pp($c)) };
172*2b15cb3dSCy Schubert}
173*2b15cb3dSCy Schubert
174*2b15cb3dSCy Schubertsub mapwords(&@) {
175*2b15cb3dSCy Schubert    my ($f, @l) = @_;
176*2b15cb3dSCy Schubert    my @res;
177*2b15cb3dSCy Schubert    for my $el (@l) {
178*2b15cb3dSCy Schubert        local $_ = $el;
179*2b15cb3dSCy Schubert        push @res, $el =~ /^(?:[,\.\{\}\(\):;\[\]\|])$/ || ref $el eq 'ARRAY' ?
180*2b15cb3dSCy Schubert                    $el : $f->();
181*2b15cb3dSCy Schubert    }
182*2b15cb3dSCy Schubert    return @res;
183*2b15cb3dSCy Schubert}
184*2b15cb3dSCy Schubert
185*2b15cb3dSCy Schubertmy %macros;
186*2b15cb3dSCy Schubert
187*2b15cb3dSCy Schubert###############################################################################
188*2b15cb3dSCy Schubert
189*2b15cb3dSCy Schubert# Default macro definitions start
190*2b15cb3dSCy Schubert
191*2b15cb3dSCy Schubert###############################################################################
192*2b15cb3dSCy Schubert
193*2b15cb3dSCy Schubertdef_macro('Xo',  sub { @_ }, concat_until => '.Xc');
194*2b15cb3dSCy Schubert
195*2b15cb3dSCy Schubertdef_macro('.Ns', sub {ns, @_});
196*2b15cb3dSCy Schubertdef_macro('Ns',  sub {ns, @_});
197*2b15cb3dSCy Schubert
198*2b15cb3dSCy Schubert{
199*2b15cb3dSCy Schubert    my %reference;
200*2b15cb3dSCy Schubert    def_macro('.Rs', sub { () } );
201*2b15cb3dSCy Schubert    def_macro('.%A', sub {
202*2b15cb3dSCy Schubert        if ($reference{authors}) {
203*2b15cb3dSCy Schubert            $reference{authors} .= " and @_"
204*2b15cb3dSCy Schubert        }
205*2b15cb3dSCy Schubert        else {
206*2b15cb3dSCy Schubert            $reference{authors} = "@_";
207*2b15cb3dSCy Schubert        }
208*2b15cb3dSCy Schubert        return ();
209*2b15cb3dSCy Schubert    });
210*2b15cb3dSCy Schubert    def_macro('.%T', sub { $reference{title} = "@_"; () } );
211*2b15cb3dSCy Schubert    def_macro('.%O', sub { $reference{optional} = "@_"; () } );
212*2b15cb3dSCy Schubert
213*2b15cb3dSCy Schubert    sub set_Re_callback {
214*2b15cb3dSCy Schubert        my ($sub) = @_;
215*2b15cb3dSCy Schubert        croak 'Not a CODE reference' if not ref $sub eq 'CODE';
216*2b15cb3dSCy Schubert        def_macro('.Re', sub {
217*2b15cb3dSCy Schubert            my @ret = $sub->(\%reference);
218*2b15cb3dSCy Schubert            %reference = (); @ret
219*2b15cb3dSCy Schubert        });
220*2b15cb3dSCy Schubert        return;
221*2b15cb3dSCy Schubert    }
222*2b15cb3dSCy Schubert}
223*2b15cb3dSCy Schubert
224*2b15cb3dSCy Schubertdef_macro('.Bl', sub { die '.Bl - no list callback set' });
225*2b15cb3dSCy Schubertdef_macro('.It', sub { die ".It called outside of list context - maybe near line $." });
226*2b15cb3dSCy Schubertdef_macro('.El', sub { die '.El requires .Bl first' });
227*2b15cb3dSCy Schubert
228*2b15cb3dSCy Schubert
229*2b15cb3dSCy Schubert{
230*2b15cb3dSCy Schubert    my $elcb = sub { () };
231*2b15cb3dSCy Schubert
232*2b15cb3dSCy Schubert    sub set_El_callback {
233*2b15cb3dSCy Schubert        my ($sub) = @_;
234*2b15cb3dSCy Schubert        croak 'Not a CODE reference' if ref $sub ne 'CODE';
235*2b15cb3dSCy Schubert        $elcb = $sub;
236*2b15cb3dSCy Schubert        return;
237*2b15cb3dSCy Schubert    }
238*2b15cb3dSCy Schubert
239*2b15cb3dSCy Schubert    sub set_Bl_callback {
240*2b15cb3dSCy Schubert        my ($blcb, %defs) = @_;
241*2b15cb3dSCy Schubert        croak 'Not a CODE reference' if ref $blcb ne 'CODE';
242*2b15cb3dSCy Schubert        def_macro('.Bl', sub {
243*2b15cb3dSCy Schubert
244*2b15cb3dSCy Schubert            my $orig_it   = get_macro('.It');
245*2b15cb3dSCy Schubert            my $orig_el   = get_macro('.El');
246*2b15cb3dSCy Schubert            my $orig_bl   = get_macro('.Bl');
247*2b15cb3dSCy Schubert            my $orig_elcb = $elcb;
248*2b15cb3dSCy Schubert
249*2b15cb3dSCy Schubert            # Restore previous .It and .El on each .El
250*2b15cb3dSCy Schubert            def_macro('.El', sub {
251*2b15cb3dSCy Schubert                    def_macro('.El', delete $orig_el->{run}, %$orig_el);
252*2b15cb3dSCy Schubert                    def_macro('.It', delete $orig_it->{run}, %$orig_it);
253*2b15cb3dSCy Schubert                    def_macro('.Bl', delete $orig_bl->{run}, %$orig_bl);
254*2b15cb3dSCy Schubert                    my @ret = $elcb->(@_);
255*2b15cb3dSCy Schubert                    $elcb = $orig_elcb;
256*2b15cb3dSCy Schubert                    @ret
257*2b15cb3dSCy Schubert                });
258*2b15cb3dSCy Schubert            $blcb->(@_)
259*2b15cb3dSCy Schubert        }, %defs);
260*2b15cb3dSCy Schubert        return;
261*2b15cb3dSCy Schubert    }
262*2b15cb3dSCy Schubert}
263*2b15cb3dSCy Schubert
264*2b15cb3dSCy Schubertdef_macro('.Sm', sub {
265*2b15cb3dSCy Schubert    my ($arg) = @_;
266*2b15cb3dSCy Schubert    if (defined $arg) {
267*2b15cb3dSCy Schubert        space($arg);
268*2b15cb3dSCy Schubert    } else {
269*2b15cb3dSCy Schubert        space() eq 'off' ?
270*2b15cb3dSCy Schubert            space('on') :
271*2b15cb3dSCy Schubert            space('off');
272*2b15cb3dSCy Schubert    }
273*2b15cb3dSCy Schubert    ()
274*2b15cb3dSCy Schubert} );
275*2b15cb3dSCy Schubertdef_macro('Sm', do { my $off; sub {
276*2b15cb3dSCy Schubert    my ($arg) = @_;
277*2b15cb3dSCy Schubert    if (defined $arg && $arg =~ /^(on|off)$/) {
278*2b15cb3dSCy Schubert        shift;
279*2b15cb3dSCy Schubert        if    ($arg eq 'off') { soff, @_; }
280*2b15cb3dSCy Schubert        elsif ($arg eq 'on')  { son, @_; }
281*2b15cb3dSCy Schubert    }
282*2b15cb3dSCy Schubert    else {
283*2b15cb3dSCy Schubert        stoggle, @_;
284*2b15cb3dSCy Schubert    }
285*2b15cb3dSCy Schubert}} );
286*2b15cb3dSCy Schubert
287*2b15cb3dSCy Schubert###############################################################################
288*2b15cb3dSCy Schubert
289*2b15cb3dSCy Schubert# Default macro definitions end
290*2b15cb3dSCy Schubert
291*2b15cb3dSCy Schubert###############################################################################
292*2b15cb3dSCy Schubert
293*2b15cb3dSCy Schubertsub def_macro {
294*2b15cb3dSCy Schubert    croak 'Odd number of elements for hash argument <'.(scalar @_).'>' if @_%2;
295*2b15cb3dSCy Schubert    my ($macro, $sub, %def) = @_;
296*2b15cb3dSCy Schubert    croak 'Not a CODE reference' if ref $sub ne 'CODE';
297*2b15cb3dSCy Schubert
298*2b15cb3dSCy Schubert    $macros{ $macro } = {
299*2b15cb3dSCy Schubert        run          => $sub,
300*2b15cb3dSCy Schubert        greedy       => delete $def{greedy} || 0,
301*2b15cb3dSCy Schubert        raw          => delete $def{raw}    || 0,
302*2b15cb3dSCy Schubert        concat_until => delete $def{concat_until},
303*2b15cb3dSCy Schubert    };
304*2b15cb3dSCy Schubert    if ($macros{ $macro }{concat_until}) {
305*2b15cb3dSCy Schubert        $macros{ $macros{ $macro }{concat_until} } = { run => sub { @_ } };
306*2b15cb3dSCy Schubert        $macros{ $macro }{greedy}                  = 1;
307*2b15cb3dSCy Schubert    }
308*2b15cb3dSCy Schubert    return;
309*2b15cb3dSCy Schubert}
310*2b15cb3dSCy Schubert
311*2b15cb3dSCy Schubertsub get_macro {
312*2b15cb3dSCy Schubert    my ($macro) = @_;
313*2b15cb3dSCy Schubert    croak "Macro <$macro> not defined" if not exists $macros{ $macro };
314*2b15cb3dSCy Schubert    +{ %{ $macros{ $macro } } }
315*2b15cb3dSCy Schubert}
316*2b15cb3dSCy Schubert
317*2b15cb3dSCy Schubert#TODO: document this
318*2b15cb3dSCy Schubertsub parse_opts {
319*2b15cb3dSCy Schubert    my %args;
320*2b15cb3dSCy Schubert    my $last;
321*2b15cb3dSCy Schubert    for (@_) {
322*2b15cb3dSCy Schubert        if ($_ =~ /^\\?-/) {
323*2b15cb3dSCy Schubert            s/^\\?-//;
324*2b15cb3dSCy Schubert            $args{$_} = 1;
325*2b15cb3dSCy Schubert            $last = _unquote($_);
326*2b15cb3dSCy Schubert        }
327*2b15cb3dSCy Schubert        else {
328*2b15cb3dSCy Schubert            $args{$last} = _unquote($_) if $last;
329*2b15cb3dSCy Schubert            undef $last;
330*2b15cb3dSCy Schubert        }
331*2b15cb3dSCy Schubert    }
332*2b15cb3dSCy Schubert    return %args;
333*2b15cb3dSCy Schubert}
334*2b15cb3dSCy Schubert
335*2b15cb3dSCy Schubertsub _is_control {
336*2b15cb3dSCy Schubert    my ($el, $expected) = @_;
337*2b15cb3dSCy Schubert    if (defined $expected) {
338*2b15cb3dSCy Schubert        ref $el eq 'ARRAY' and $el->[0] eq $expected;
339*2b15cb3dSCy Schubert    }
340*2b15cb3dSCy Schubert    else {
341*2b15cb3dSCy Schubert        ref $el eq 'ARRAY';
342*2b15cb3dSCy Schubert    }
343*2b15cb3dSCy Schubert}
344*2b15cb3dSCy Schubert
345*2b15cb3dSCy Schubert{
346*2b15cb3dSCy Schubert    my $sep = ' ';
347*2b15cb3dSCy Schubert
348*2b15cb3dSCy Schubert    sub to_string {
349*2b15cb3dSCy Schubert        if (@_ > 0) {
350*2b15cb3dSCy Schubert            # Handle punctunation
351*2b15cb3dSCy Schubert            my ($in_brace, @punct) = '';
352*2b15cb3dSCy Schubert            my @new = map {
353*2b15cb3dSCy Schubert                if (/^([\[\(])$/) {
354*2b15cb3dSCy Schubert                    ($in_brace = $1) =~ tr/([/)]/;
355*2b15cb3dSCy Schubert                    $_, ns
356*2b15cb3dSCy Schubert                }
357*2b15cb3dSCy Schubert                elsif (/^([\)\]])$/ && $in_brace eq $1) {
358*2b15cb3dSCy Schubert                    $in_brace = '';
359*2b15cb3dSCy Schubert                    ns, $_
360*2b15cb3dSCy Schubert                }
361*2b15cb3dSCy Schubert                elsif ($_ =~ /^[,\.;:\?\!\)\]]$/) {
362*2b15cb3dSCy Schubert                    push @punct, ns, $_;
363*2b15cb3dSCy Schubert                    ();
364*2b15cb3dSCy Schubert                }
365*2b15cb3dSCy Schubert                elsif (_is_control($_, 'pp')) {
366*2b15cb3dSCy Schubert                    $_->[1]
367*2b15cb3dSCy Schubert                }
368*2b15cb3dSCy Schubert                elsif (_is_control($_)) {
369*2b15cb3dSCy Schubert                    $_
370*2b15cb3dSCy Schubert                }
371*2b15cb3dSCy Schubert                else {
372*2b15cb3dSCy Schubert                    splice (@punct), $_;
373*2b15cb3dSCy Schubert                }
374*2b15cb3dSCy Schubert            } @_;
375*2b15cb3dSCy Schubert            push @new, @punct;
376*2b15cb3dSCy Schubert
377*2b15cb3dSCy Schubert            # Produce string out of an array dealing with the special control characters
378*2b15cb3dSCy Schubert            # space('off') must but one character delayed
379*2b15cb3dSCy Schubert            my ($no_space, $space_off) = 1;
380*2b15cb3dSCy Schubert            my $res = '';
381*2b15cb3dSCy Schubert            while (defined(my $el = shift @new)) {
382*2b15cb3dSCy Schubert                if    (_is_control($el, 'hardspace'))   { $no_space = 1; $res .= ' ' }
383*2b15cb3dSCy Schubert                elsif (_is_control($el, 'nospace'))     { $no_space = 1;             }
384*2b15cb3dSCy Schubert                elsif (_is_control($el, 'spaceoff'))    { $space_off = 1;            }
385*2b15cb3dSCy Schubert                elsif (_is_control($el, 'spaceon'))     { space('on');               }
386*2b15cb3dSCy Schubert                elsif (_is_control($el, 'spacetoggle')) { space() eq 'on' ?
387*2b15cb3dSCy Schubert                                                            $space_off = 1 :
388*2b15cb3dSCy Schubert                                                            space('on')              }
389*2b15cb3dSCy Schubert                else {
390*2b15cb3dSCy Schubert                    if ($no_space) {
391*2b15cb3dSCy Schubert                        $no_space = 0;
392*2b15cb3dSCy Schubert                        $res .= "$el"
393*2b15cb3dSCy Schubert                    }
394*2b15cb3dSCy Schubert                    else {
395*2b15cb3dSCy Schubert                        $res .= "$sep$el"
396*2b15cb3dSCy Schubert                    }
397*2b15cb3dSCy Schubert
398*2b15cb3dSCy Schubert                    if ($space_off)    { space('off'); $space_off = 0; }
399*2b15cb3dSCy Schubert                }
400*2b15cb3dSCy Schubert            }
401*2b15cb3dSCy Schubert            $res
402*2b15cb3dSCy Schubert        }
403*2b15cb3dSCy Schubert        else {
404*2b15cb3dSCy Schubert            '';
405*2b15cb3dSCy Schubert        }
406*2b15cb3dSCy Schubert    }
407*2b15cb3dSCy Schubert
408*2b15cb3dSCy Schubert    sub space {
409*2b15cb3dSCy Schubert        my ($arg) = @_;
410*2b15cb3dSCy Schubert        if (defined $arg && $arg =~ /^(on|off)$/) {
411*2b15cb3dSCy Schubert            $sep = ' ' if $arg eq 'on';
412*2b15cb3dSCy Schubert            $sep = ''  if $arg eq 'off';
413*2b15cb3dSCy Schubert            return;
414*2b15cb3dSCy Schubert        }
415*2b15cb3dSCy Schubert        else {
416*2b15cb3dSCy Schubert            return $sep eq '' ? 'off' : 'on';
417*2b15cb3dSCy Schubert        }
418*2b15cb3dSCy Schubert    }
419*2b15cb3dSCy Schubert}
420*2b15cb3dSCy Schubert
421*2b15cb3dSCy Schubertsub _unquote {
422*2b15cb3dSCy Schubert    my @args = @_;
423*2b15cb3dSCy Schubert    $_ =~ s/^"([^"]+)"$/$1/g for @args;
424*2b15cb3dSCy Schubert    wantarray ? @args : $args[0];
425*2b15cb3dSCy Schubert}
426*2b15cb3dSCy Schubert
427*2b15cb3dSCy Schubertsub call_macro {
428*2b15cb3dSCy Schubert    my ($macro, @args) = @_;
429*2b15cb3dSCy Schubert    my @ret;
430*2b15cb3dSCy Schubert
431*2b15cb3dSCy Schubert    my @newargs;
432*2b15cb3dSCy Schubert    my $i = 0;
433*2b15cb3dSCy Schubert
434*2b15cb3dSCy Schubert    @args = _unquote(@args) if (!$macros{ $macro }{raw});
435*2b15cb3dSCy Schubert
436*2b15cb3dSCy Schubert    # Call any callable macros in the argument list
437*2b15cb3dSCy Schubert    for (@args) {
438*2b15cb3dSCy Schubert        if ($_ =~ /^[A-Z][a-z]+$/ && exists $macros{ $_ }) {
439*2b15cb3dSCy Schubert            push @ret, call_macro($_, @args[$i+1 .. $#args]);
440*2b15cb3dSCy Schubert            last;
441*2b15cb3dSCy Schubert        } else {
442*2b15cb3dSCy Schubert            if ($macros{ $macro }{greedy}) {
443*2b15cb3dSCy Schubert                push @ret, $_;
444*2b15cb3dSCy Schubert            }
445*2b15cb3dSCy Schubert            else {
446*2b15cb3dSCy Schubert                push @newargs, $_;
447*2b15cb3dSCy Schubert            }
448*2b15cb3dSCy Schubert        }
449*2b15cb3dSCy Schubert        $i++;
450*2b15cb3dSCy Schubert    }
451*2b15cb3dSCy Schubert
452*2b15cb3dSCy Schubert    if ($macros{ $macro }{concat_until}) {
453*2b15cb3dSCy Schubert        my ($n_macro, @n_args) = ('');
454*2b15cb3dSCy Schubert        while (1) {
455*2b15cb3dSCy Schubert            die "EOF was reached and no $macros{ $macro }{concat_until} found"
456*2b15cb3dSCy Schubert                if not defined $n_macro;
457*2b15cb3dSCy Schubert            ($n_macro, @n_args) = parse_line(undef, sub { push @ret, shift });
458*2b15cb3dSCy Schubert            if ($n_macro eq $macros{ $macro }{concat_until}) {
459*2b15cb3dSCy Schubert                push @ret, call_macro($n_macro, @n_args);
460*2b15cb3dSCy Schubert                last;
461*2b15cb3dSCy Schubert            }
462*2b15cb3dSCy Schubert            else {
463*2b15cb3dSCy Schubert                $n_macro =~ s/^\.//;
464*2b15cb3dSCy Schubert                push @ret, call_macro($n_macro, @n_args) if exists $macros{ $n_macro };
465*2b15cb3dSCy Schubert            }
466*2b15cb3dSCy Schubert        }
467*2b15cb3dSCy Schubert    }
468*2b15cb3dSCy Schubert
469*2b15cb3dSCy Schubert    if ($macros{ $macro }{greedy}) {
470*2b15cb3dSCy Schubert        #print "MACROG $macro (", (join ', ', @ret), ")\n";
471*2b15cb3dSCy Schubert        return $macros{ $macro }{run}->(@ret);
472*2b15cb3dSCy Schubert    }
473*2b15cb3dSCy Schubert    else {
474*2b15cb3dSCy Schubert        #print "MACRO $macro (", (join ', ', @newargs), ")".(join ', ', @ret)."\n";
475*2b15cb3dSCy Schubert        return $macros{ $macro }{run}->(@newargs), @ret;
476*2b15cb3dSCy Schubert    }
477*2b15cb3dSCy Schubert}
478*2b15cb3dSCy Schubert
479*2b15cb3dSCy Schubert{
480*2b15cb3dSCy Schubert    my ($in_fh, $out_sub, $preprocess_sub);
481*2b15cb3dSCy Schubert    sub parse_line {
482*2b15cb3dSCy Schubert        $in_fh          = $_[0] if defined $_[0] || !defined $in_fh;
483*2b15cb3dSCy Schubert        $out_sub        = $_[1] if defined $_[1] || !defined $out_sub;
484*2b15cb3dSCy Schubert        $preprocess_sub = $_[2] if defined $_[2] || !defined $preprocess_sub;
485*2b15cb3dSCy Schubert
486*2b15cb3dSCy Schubert        croak 'out_sub not a CODE reference'
487*2b15cb3dSCy Schubert            if not ref $out_sub eq 'CODE';
488*2b15cb3dSCy Schubert        croak 'preprocess_sub not a CODE reference'
489*2b15cb3dSCy Schubert            if defined $preprocess_sub && not ref $preprocess_sub eq 'CODE';
490*2b15cb3dSCy Schubert
491*2b15cb3dSCy Schubert        while (my $line = <$in_fh>) {
492*2b15cb3dSCy Schubert            chomp $line;
493*2b15cb3dSCy Schubert            if ($line =~ /^\.[A-z][a-z0-9]+/ || $line =~ /^\.%[A-Z]/ ||
494*2b15cb3dSCy Schubert                $line =~ /^\.\\"/)
495*2b15cb3dSCy Schubert            {
496*2b15cb3dSCy Schubert                $line =~ s/ +/ /g;
497*2b15cb3dSCy Schubert                my ($macro, @args) = quotewords(' ', 1, $line);
498*2b15cb3dSCy Schubert                @args = grep { defined $_ } @args;
499*2b15cb3dSCy Schubert                $preprocess_sub->(@args) if defined $preprocess_sub;
500*2b15cb3dSCy Schubert                if ($macro && exists $macros{ $macro }) {
501*2b15cb3dSCy Schubert                    return ($macro, @args);
502*2b15cb3dSCy Schubert                } else {
503*2b15cb3dSCy Schubert                    $out_sub->($line);
504*2b15cb3dSCy Schubert                }
505*2b15cb3dSCy Schubert            }
506*2b15cb3dSCy Schubert            else {
507*2b15cb3dSCy Schubert                $out_sub->($line);
508*2b15cb3dSCy Schubert            }
509*2b15cb3dSCy Schubert        }
510*2b15cb3dSCy Schubert        return;
511*2b15cb3dSCy Schubert    }
512*2b15cb3dSCy Schubert}
513*2b15cb3dSCy Schubert
514*2b15cb3dSCy Schubert1;
515*2b15cb3dSCy Schubert__END__
516