36
37:- module(atom,
38 [ restyle_identifier/3, 39 identifier_parts/2, 40 join_identifier_parts/3 41 ]). 42:- use_module(library(apply)).
52
65
66restyle_identifier(Style, In, Out) :-
67 identifier_parts(In, Parts),
68 join_identifier_parts(Style, Parts, Out).
80identifier_parts(';', [';']) :- !.
81identifier_parts('|', ['|']) :- !.
82identifier_parts('!', ['!']) :- !.
83identifier_parts(',', [',']) :- !.
84identifier_parts(Name, Parts) :-
85 atom_codes(Name, Codes),
86 ( phrase(identifier_parts(Parts), Codes)
87 -> true
88 ; maplist(is_symbol_code, Codes)
89 -> Parts = [Name]
90 ).
91
92is_symbol_code(Code) :-
93 code_type(Code, prolog_symbol).
94
95identifier_parts([H|T]) -->
96 identifier_part(H),
97 !,
98 identifier_parts(T).
99identifier_parts([]) --> [].
100
101identifier_part(H) -->
102 string(Codes, Tail),
103 sep(Tail),
104 !,
105 { Codes = [_|_],
106 atom_codes(H0, Codes),
107 ( maplist(is_upper, Codes)
108 -> H = H0
109 ; downcase_atom(H0, H)
110 )
111 }.
112
113string(T,T) --> [].
114string([H|T], L) --> [H], string(T, L).
115
116sep([]) --> sep_char, !, sep_chars.
117sep([T]), [N] -->
118 [T,N],
119 { code_type(T, lower),
120 code_type(N, upper)
121 }.
122sep([],[],[]).
123
124sep_char -->
125 [H],
126 { \+ code_type(H, alnum) }.
127
128sep_chars --> sep_char, !, sep_chars.
129sep_chars --> [].
147join_identifier_parts(Style, [First|Parts], Identifier) :-
148 style(Style, CapFirst, CapRest, Sep),
149 capitalise(CapFirst, First, H),
150 maplist(capitalise(CapRest), Parts, T),
151 atomic_list_concat([H|T], Sep, Identifier).
155style('OneTwo', true, true, '').
156style(oneTwo, false, true, '').
157style(one_two, false, false, '_').
158style('One_Two', true, true, '_').
159style(style(CFirst, CRest, Sep), CFirst, CRest, Sep).
160
161capitalise(false, X, X) :- !.
162capitalise(true, X, Y) :-
163 atom_codes(X, [H0|T]),
164 code_type(H0, to_lower(H)),
165 atom_codes(Y, [H|T])
Operations on atoms
This library provides operations on atoms that are not covered by builtin predicates. The current implementation is just a start, making code developed in xpce and duplicated in various projects reusable. */