34
   35:- module(prolog_format,
   36          [ format_spec/2,                         37            format_spec//1,                        38            format_types/2                         39          ]).   40:- autoload(library(error),[existence_error/2]).   41:- autoload(library(dcg/basics),[eos//0,string_without//2,integer//1]).
   73format_spec(Format, Spec) :-
   74    (   is_list(Format)
   75    ->  Codes = Format
   76    ;   string_codes(Format, Codes)
   77    ),
   78    phrase(format_spec(Spec), Codes).
   85format_spec([escape(Numeric,Modifier,Action)|Rest]) -->
   86    "~",
   87    !,
   88    numeric_argument(Numeric),
   89    modifier_argument(Modifier),
   90    action(Action),
   91    format_spec(Rest).
   92format_spec([text(String)|Rest]) -->
   93    string_without("~", Codes),
   94    { Codes \== [],
   95      !,
   96      string_codes(String, Codes)
   97    },
   98    format_spec(Rest).
   99format_spec([]) -->
  100    [].
  109format_types(Format, Types) :-
  110    format_spec(Format, Spec),
  111    spec_types(Spec, Types).
  119spec_types(Spec, Types) :-
  120    phrase(spec_types(Spec), Types).
  121
  122spec_types([]) -->
  123    [].
  124spec_types([Item|Items]) -->
  125    item_types(Item),
  126    spec_types(Items).
  127
  128item_types(text(_)) -->
  129    [].
  130item_types(escape(Numeric,_,Action)) -->
  131    numeric_types(Numeric),
  132    action_types(Action).
  133
  134numeric_types(number(_)) -->
  135    [].
  136numeric_types(character(_)) -->
  137    [].
  138numeric_types(star) -->
  139    [number].
  140numeric_types(nothing) -->
  141    [].
  142
  143action_types(Action) -->
  144    { atom_codes(Action, [Code]) },
  145    { action_types(Code, Types) },
  146    phrase(Types).
  147
  148numeric_argument(number(N)) -->
  149    integer(N),
  150    !.
  151numeric_argument(character(C)) -->
  152    "`",
  153    !,
  154    [C].
  155numeric_argument(star) -->
  156    "*",
  157    !.
  158numeric_argument(nothing) -->
  159    "".
  160
  161modifier_argument(colon) -->
  162    ":".
  163modifier_argument(no_colon) -->
  164    \+ ":".
  165
  166action(Char) -->
  167    [C],
  168    { char_code(Char, C),
  169      (   is_action(C)
  170      ->  true
  171      ;   existence_error(format_character, Char)
  172      )
  173    }.
  181is_action(Action) :-
  182    action_types(Action, _).
  194action_types(0'~, []).
  195action_types(0'a, [atom]).
  196action_types(0'c, [integer]).    197action_types(0'd, [integer]).
  198action_types(0'D, [integer]).
  199action_types(0'e, [float]).
  200action_types(0'E, [float]).
  201action_types(0'f, [float]).
  202action_types(0'g, [float]).
  203action_types(0'G, [float]).
  204action_types(0'i, [any]).
  205action_types(0'I, [integer]).
  206action_types(0'k, [any]).
  207action_types(0'n, []).
  208action_types(0'N, []).
  209action_types(0'p, [any]).
  210action_types(0'q, [any]).
  211action_types(0'r, [integer]).
  212action_types(0'R, [integer]).
  213action_types(0's, [text]).
  214action_types(0'@, [callable]).
  215action_types(0't, []).
  216action_types(0'|, []).
  217action_types(0'+, []).
  218action_types(0'w, [any]).
  219action_types(0'W, [any, list])
 
Analyse format specifications
This library parses the format specification used by format/1, format/2 and format/3. The parsed specification can be used to validate the consistency of the format string and the provided arguments. For example:
?- format_types('~d bottles of beer', Types). Types = [integer].