36
37:- module(atom,
38 [ restyle_identifier/3, 39 identifier_parts/2, 40 join_identifier_parts/3 41 ]). 42:- autoload(library(apply),[maplist/2,maplist/3]). 43:- autoload(library(ctypes),[is_upper/1]).
54
67
68restyle_identifier(Style, In, Out) :-
69 identifier_parts(In, Parts),
70 join_identifier_parts(Style, Parts, Out).
82identifier_parts(';', [';']) :- !.
83identifier_parts('|', ['|']) :- !.
84identifier_parts('!', ['!']) :- !.
85identifier_parts(',', [',']) :- !.
86identifier_parts(Name, Parts) :-
87 atom_codes(Name, Codes),
88 ( phrase(identifier_parts(Parts), Codes)
89 -> true
90 ; maplist(is_symbol_code, Codes)
91 -> Parts = [Name]
92 ).
93
94is_symbol_code(Code) :-
95 code_type(Code, prolog_symbol).
96
97identifier_parts([H|T]) -->
98 identifier_part(H),
99 !,
100 identifier_parts(T).
101identifier_parts([]) --> [].
102
103identifier_part(H) -->
104 string(Codes, Tail),
105 sep(Tail),
106 !,
107 { Codes = [_|_],
108 atom_codes(H0, Codes),
109 ( maplist(is_upper, Codes)
110 -> H = H0
111 ; downcase_atom(H0, H)
112 )
113 }.
114
115string(T,T) --> [].
116string([H|T], L) --> [H], string(T, L).
117
118sep([]) --> sep_char, !, sep_chars.
119sep([T]), [N] -->
120 [T,N],
121 { code_type(T, lower),
122 code_type(N, upper)
123 }.
124sep([],[],[]).
125
126sep_char -->
127 [H],
128 { \+ code_type(H, alnum) }.
129
130sep_chars --> sep_char, !, sep_chars.
131sep_chars --> [].
149join_identifier_parts(Style, [First|Parts], Identifier) :-
150 style(Style, CapFirst, CapRest, Sep),
151 capitalise(CapFirst, First, H),
152 maplist(capitalise(CapRest), Parts, T),
153 atomic_list_concat([H|T], Sep, Identifier).
157style('OneTwo', true, true, '').
158style(oneTwo, false, true, '').
159style(one_two, false, false, '_').
160style('One_Two', true, true, '_').
161style(style(CFirst, CRest, Sep), CFirst, CRest, Sep).
162
163capitalise(false, X, X) :- !.
164capitalise(true, X, Y) :-
165 atom_codes(X, [H0|T]),
166 code_type(H0, to_lower(H)),
167 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. */