35
   36:- module(noble_avatar,
   37	  [ noble_avatar/2,			   38	    noble_avatar/3,			   39	    create_avatar/2,			   40
   41	    existing_noble_avatar/2		   42	  ]).   43:- use_module(library(apply)).   44:- use_module(library(lists)).   45:- use_module(library(random)).   46:- use_module(library(filesex)).   47:- use_module(library(process)).   48
   74
   75
   76:- multifile
   77	user:file_search_path/2.   78
   79user:file_search_path(noble,		       icons(noble)).
   80user:file_search_path(noble_avatar_components, noble(components)).
   81user:file_search_path(noble_avatar,	       data(avatars)).
   82
   83:- dynamic
   84	noble_dir/1,				   85	noble/4.				   86
   98
   99noble_avatar(Gender, Image) :-
  100	noble_avatar(Gender, Image, _).
  101
  102noble_avatar(Gender, Image, New) :-
  103	var(New), !,
  104	noble_index_components,
  105	avatar_components(Gender, IDs, Components),
  106	maplist(plus(0'a), IDs, Codes),
  107	atom_codes(Base, Codes),
  108	file_name_extension(Base, png, PNG),
  109	with_mutex(noble_avatar,
  110		   create_avatar_sync(Components,
  111				      noble_avatar, PNG, Image, New)).
  112noble_avatar(Gender, Image, true) :- !,
  113	repeat,
  114	    noble_avatar(Gender, Image, New),
  115	    New == true, !.
  116
  120
  121create_avatar(PNG, Image) :-
  122	file_name_extension(Base, png, PNG),
  123	atom_codes(Base, Codes),
  124	maplist(plus(0'a), IDs, Codes),
  125	noble_index_components,
  126	avatar_components(_Gender, IDs, Components),
  127	with_mutex(noble_avatar,
  128		   create_avatar_sync(Components,
  129				      noble_avatar, PNG, Image, _New)).
  130
  135
  136existing_noble_avatar(Gender, Image) :-
  137	absolute_file_name(noble_avatar(.), Dir,
  138			   [ file_type(directory),
  139			     solutions(all)
  140			   ]),
  141	directory_files(Dir, Files),
  142	member(Image, Files),
  143	file_name_extension(Base, png, Image),
  144	sub_atom(Base, 0, 1, _, First),
  145	char_code(First, Code),
  146	Index is Code-0'a,
  147	gender_id(Gender, Index).
  148
  149
  150create_avatar_sync(Components, DirAlias, File, Image, New) :-
  151	Location =.. [DirAlias,File],
  152	(   absolute_file_name(Location, Image,
  153			       [ access(read),
  154				 file_errors(fail)
  155			       ])
  156	->  New = false
  157	;   absolute_file_name(Location, Image,
  158			       [ access(write), file_errors(fail) ])
  159	->  composite(Components, Image),
  160	    New	= true
  161	;   Dir =.. [DirAlias,.],
  162	    absolute_file_name(Dir, DirPath, [solutions(all)]),
  163	    file_directory_name(DirPath, Parent),
  164	    exists_directory(Parent),
  165	    \+ exists_directory(DirPath)
  166	->  make_directory(DirPath),
  167	    absolute_file_name(Location, Image, [access(write)]),
  168	    composite(Components, Image)
  169	).
  170
  171composite(Components, Image) :-
  172	noble_dir(Dir),
  173	phrase(composite(Components, Dir), Argv, [file(Image)]),
  174	process_create(path(convert), Argv, []).
  175
  176composite([], _) -->
  177	[ '-background', 'none', '-flatten' ].
  178composite([File|T], Dir) -->
  179	{ directory_file_path(Dir, File, AbsFile)
  180	},
  181	[ '-page', '+0+0', file(AbsFile) ],
  182	composite(T, Dir).
  183
  184avatar_components(Gender, [GID|IDs], Files) :-
  185	gender_id(Gender, GID),
  186	parts(Parts),
  187	files(Parts, Gender, IDs, Files).
  188
  189files([], _, [], []).
  190files([P:H-Gender|T], Gender, [I|IDs], [File|Files]) :-
  191	(   var(I), I \== 0
  192	->  maybe(P)
  193	;   true
  194	),
  195	file(H, Gender, I, File), !,
  196	files(T, Gender, IDs, Files).
  197files([_|T], Gender, [0|IDs], Files) :-
  198	files(T, Gender, IDs, Files).
  199
  200file(Part, Gender, I, File) :-
  201	findall(I, noble(Part, Gender, I, _), IL),
  202	random_member(I, IL),
  203	noble(Part, Gender, I, File).
  204
  205gender_id(Var, ID) :-
  206	var(Var), var(ID),
  207	ID is 1+random(2),
  208	gender_id(Var, ID), !.
  209gender_id(male, 1).
  210gender_id(female, 2).
  211
  212
  222
  223parts([ 0.5:pattern - _,
  224	1.0:head - _,
  225	1.0:mouth - _,
  226	1.0:eye - _,
  227	0.5:eyepatch - _,
  228	0.3:glasses - _,
  229	0.3:mustache - male,
  230	0.5:beard - male,
  231	0.8:hair - _,
  232	0.2:accessory - _,
  233	0.5:necklace - _,
  234	0.3:boa - _,
  235	0.2:scar - _,
  236	0.1:sideburn - _
  237      ]).
  238
  243
  244noble_index_components :-
  245	noble_dir(_), !.
  246noble_index_components :-
  247	with_mutex(noble_avatar, noble_index_components_sync).
  248
  249noble_index_components_sync :-
  250	noble_dir(_), !.
  251noble_index_components_sync :-
  252	retractall(noble_dir(_)),
  253	retractall(noble(_,_,_,_)),
  254	absolute_file_name(noble_avatar_components(.), Dir,
  255			   [ file_type(directory)
  256			   ]),
  257	directory_files(Dir, Files),
  258	maplist(noble_file, Files),
  259	assertz(noble_dir(Dir)).
  260
  261noble_file(File) :-
  262	file_name_extension(Base, png, File),
  263	atomic_list_concat([avatar,Part,V], '_', Base),
  264	(   atom_concat(f, NA, V),
  265	    atom_number(NA, N)
  266	->  Gender = female
  267	;   atom_concat(m, NA, V),
  268	    atom_number(NA, N)
  269	->  Gender = male
  270	;   atom_number(V, N)
  271	), !,
  272	assert(noble(Part, Gender, N, File)).
  273noble_file(_)