~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_pp.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
81
81
    exprs(Es, 0, Hook).
82
82
 
83
83
exprs(Es, I, Hook) ->
84
 
    map(fun(Item) -> frmt(Item, I) end, lexprs(Es, Hook)).
 
84
    frmt({seq,[],[],[$,],lexprs(Es, Hook)}, I).
85
85
 
86
86
expr(E) ->
87
87
    frmt(lexpr(E, 0, none)).
359
359
    maybe_paren(P, Prec, Item).
360
360
 
361
361
fun_info(Extra) ->
362
 
    leaf(format("% fun-info: ~p", [Extra])).
 
362
    leaf(format("% fun-info: ~w", [Extra])).
363
363
 
364
364
%% BITS:
365
365
 
585
585
%%% - {seq,Before,After,Separator,IPs}: a sequence of Is separated by 
586
586
%%%   Separator. Before is output before IPs, and the indentation of IPs 
587
587
%%%   is updated with the width of Before. After follows after IPs.
588
 
%%% - {force_el,ExtraInfo,I}: fun-info (a comment) forces linebreak before I.
 
588
%%% - {force_nl,ExtraInfo,I}: fun-info (a comment) forces linebreak before I.
589
589
%%% - {prefer_nl,Sep,IPs}: forces linebreak between Is unlesss negative
590
590
%%%   indentation.
591
591
%%% - {string,S}: a string.
594
594
%%% list, first, seq, force_nl, and prefer_nl all accept IPs, where each
595
595
%%% element is either an item or a tuple {step|cstep,I1,I2}. step means
596
596
%%% that I2 is output after linebreak and an incremented indentation.
597
 
%%% cstep works similarly, but no linebreak is the width of I1 is less
 
597
%%% cstep works similarly, but no linebreak if the width of I1 is less
598
598
%%% than the indentation (this is for "A = <expression over several lines>).
599
599
 
600
600
f([]=Nil, _I0, _ST, _WT) ->