34
35:- module(prolog_format,
36 [ format_spec/2, 37 format_spec//1, 38 format_types/2 39 ]). 40:- use_module(library(dcg/basics), [eos//0, integer//1, string_without//2]). 41:- use_module(library(when), [when/2]).
72format_spec(Format, Spec) :-
73 when((ground(Format);ground(Codes)),text_codes(Format, Codes)),
74 once(phrase(format_spec(Spec), Codes, [])).
81format_spec([]) -->
82 eos.
83format_spec([escape(Numeric,Modifier,Action)|Rest]) -->
84 "~",
85 numeric_argument(Numeric),
86 modifier_argument(Modifier),
87 action(Action),
88 format_spec(Rest).
89format_spec([text(String)|Rest]) -->
90 { when((ground(String);ground(Codes)),string_codes(String, Codes)) },
91 string_without("~", Codes),
92 { Codes \= [] },
93 format_spec(Rest).
102format_types(Format, Types) :-
103 format_spec(Format, Spec),
104 spec_types(Spec, Types).
112spec_types(Spec, Types) :-
113 phrase(spec_types(Spec), Types).
114
115spec_types([]) -->
116 [].
117spec_types([Item|Items]) -->
118 item_types(Item),
119 spec_types(Items).
120
121item_types(text(_)) -->
122 [].
123item_types(escape(Numeric,_,Action)) -->
124 numeric_types(Numeric),
125 action_types(Action).
126
127numeric_types(number(_)) -->
128 [].
129numeric_types(character(_)) -->
130 [].
131numeric_types(star) -->
132 [number].
133numeric_types(nothing) -->
134 [].
135
136action_types(Action) -->
137 { atom_codes(Action, [Code]) },
138 { action_types(Code, Types) },
139 phrase(Types).
142text_codes(Var, Codes) :-
143 var(Var),
144 !,
145 string_codes(Var, Codes).
146text_codes(Atom, Codes) :-
147 atom(Atom),
148 !,
149 atom_codes(Atom, Codes).
150text_codes(String, Codes) :-
151 string(String),
152 !,
153 string_codes(String, Codes).
154text_codes(Codes, Codes) :-
155 is_of_type(codes, Codes).
156
157
158numeric_argument(number(N)) -->
159 integer(N).
160numeric_argument(character(C)) -->
161 "`",
162 [C].
163numeric_argument(star) -->
164 "*".
165numeric_argument(nothing) -->
166 "".
167
168modifier_argument(colon) -->
169 ":".
170modifier_argument(no_colon) -->
171 \+ ":".
172
173action(Action) -->
174 [C],
175 { is_action(C) },
176 { atom_codes(Action, [C]) }.
184is_action(Action) :-
185 action_types(Action, _).
197action_types(0'~, []).
198action_types(0'a, [atom]).
199action_types(0'c, [integer]). 200action_types(0'd, [integer]).
201action_types(0'D, [integer]).
202action_types(0'e, [float]).
203action_types(0'E, [float]).
204action_types(0'f, [float]).
205action_types(0'g, [float]).
206action_types(0'G, [float]).
207action_types(0'i, [any]).
208action_types(0'I, [integer]).
209action_types(0'k, [any]).
210action_types(0'n, []).
211action_types(0'N, []).
212action_types(0'p, [any]).
213action_types(0'q, [any]).
214action_types(0'r, [integer]).
215action_types(0'R, [integer]).
216action_types(0's, [text]).
217action_types(0'@, [callable]).
218action_types(0't, []).
219action_types(0'|, []).
220action_types(0'+, []).
221action_types(0'w, [any]).
222action_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: