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