1 /* Part of XPCE --- The SWI-Prolog GUI toolkit
2
3 Author: Jan Wielemaker and Anjo Anjewierden
4 E-mail: wielemak@science.uva.nl
5 WWW: http://www.swi-prolog.org/packages/xpce/
6 Copyright (c) 1985-2005, University of Amsterdam
7 All rights reserved.
8
9 Redistribution and use in source and binary forms, with or without
10 modification, are permitted provided that the following conditions
11 are met:
12
13 1. Redistributions of source code must retain the above copyright
14 notice, this list of conditions and the following disclaimer.
15
16 2. Redistributions in binary form must reproduce the above copyright
17 notice, this list of conditions and the following disclaimer in
18 the documentation and/or other materials provided with the
19 distribution.
20
21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
32 POSSIBILITY OF SUCH DAMAGE.
33 */
34
35 #include <h/kernel.h>
36 #include <h/graphics.h>
37
38 static status defaultPostScriptFont(FontObj f);
39 static Int getPointsFont(FontObj f);
40
41 static Name
fontName(Name family,Name style,Int points)42 fontName(Name family, Name style, Int points)
43 { string s;
44 Any av[3];
45 Name rc;
46
47 av[0] = family;
48 av[1] = style;
49 av[2] = points;
50
51 str_writefv(&s, (CharArray)CtoTempString("%s_%s_%d"), 3, av);
52
53 rc = StringToName(&s);
54 str_unalloc(&s);
55
56 return rc;
57 }
58
59
60 static status
initialiseFont(FontObj f,Name family,Name style,Int points,Name xname)61 initialiseFont(FontObj f, Name family, Name style, Int points, Name xname)
62 { Name name = fontName(family, style, points);
63
64 assign(f, family, family);
65 assign(f, style, style);
66 assign(f, points, points);
67 assign(f, fixed_width, DEFAULT);
68 assign(f, iswide, DEFAULT);
69 assign(f, x_name, xname);
70
71 defaultPostScriptFont(f);
72
73 protectObject(f);
74 newAssoc(name, f);
75
76 return appendHashTable(FontTable, name, f);
77 }
78
79
80 static FontObj
getLookupFont(Class class,Name family,Name style,Int points)81 getLookupFont(Class class, Name family, Name style, Int points)
82 { Name name = fontName(family, style, points);
83 FontObj f2;
84
85 makeBuiltinFonts();
86 if ( (f2 = getMemberHashTable(FontTable, name)) )
87 answer(f2);
88
89 fail;
90 }
91
92
93 static FontObj
getConvertFont(Class class,Name name)94 getConvertFont(Class class, Name name)
95 { char *s = strName(name);
96
97 makeBuiltinFonts();
98
99 if ( s[0] == '@' )
100 { Name ref_name;
101
102 for(s++; *s == ' ' || *s == '\t'; s++)
103 ;
104 ref_name = CtoKeyword(s);
105
106 answer(getMemberHashTable(FontTable, ref_name));
107 } else
108 { DisplayObj d = CurrentDisplay(NIL);
109 FontObj f;
110 Name fn = (syntax.uppercase ? CtoKeyword(s) : name);
111
112 if ( d && (f = getMemberHashTable(d->font_table, fn)) )
113 { answer(f);
114 } else
115 { for_hash_table(FontTable, sy,
116 { FontObj f = sy->value;
117 if ( f->x_name == fn ) /* case? */
118 answer(f);
119 })
120 }
121 }
122
123 fail;
124 }
125
126
127 status
replaceFont(FontObj f,DisplayObj d)128 replaceFont(FontObj f, DisplayObj d)
129 { FontObj nofont;
130 void *wsref;
131
132 if ( !(nofont = getClassVariableValueObject(d, NAME_noFont)) )
133 errorPce(f, NAME_noDefaultFont);
134
135 if ( !(wsref = getXrefObject(nofont, d)) )
136 fail;
137
138 errorPce(f, NAME_replacedFont, nofont);
139 registerXrefObject(f, d, wsref);
140
141 assign(f, fixed_width, nofont->fixed_width);
142
143 succeed;
144 }
145
146
147 static int XopenNesting = 0;
148
149 static status
XopenFont(FontObj f,DisplayObj d)150 XopenFont(FontObj f, DisplayObj d)
151 { if ( isDefault(d) )
152 d = CurrentDisplay(f);
153
154 makeBuiltinFonts();
155
156 if ( XopenNesting > 1 )
157 fail;
158
159 XopenNesting++;
160 if ( !ws_create_font(f, d) )
161 { status rc;
162
163 errorPce(f, NAME_noRelatedXFont);
164 rc = replaceFont(f, d);
165 XopenNesting--;
166
167 return rc;
168 }
169
170 XopenNesting--;
171 succeed;
172 }
173
174
175 static status
XcloseFont(FontObj f,DisplayObj d)176 XcloseFont(FontObj f, DisplayObj d)
177 { ws_destroy_font(f, d);
178
179 succeed;
180 }
181
182
183 status
makeBuiltinFonts(void)184 makeBuiltinFonts(void)
185 { DisplayObj d;
186 static int done = FALSE;
187
188 if ( done )
189 succeed;
190 done = TRUE;
191
192 if ( (d = CurrentDisplay(NIL)) &&
193 send(d, NAME_loadFonts, EAV) && /* XPCE predefined fonts */
194 ws_system_fonts(d) && /* Window-system fonts */
195 send(d, NAME_loadFontAliases, NAME_systemFonts, EAV) )
196 { send(d, NAME_loadFontAliases, NAME_userFonts, EAV);
197 succeed;
198 }
199
200 fail;
201 }
202
203 /********************************
204 * POSTSCRIPT *
205 ********************************/
206
207 static status
defaultPostScriptFont(FontObj f)208 defaultPostScriptFont(FontObj f)
209 { char buf[LINESIZE];
210
211 if ( f->family == NAME_helvetica )
212 { strcpy(buf, "Helvetica");
213
214 if ( f->style == NAME_bold )
215 strcat(buf, "-Bold");
216 else if ( f->style == NAME_oblique )
217 strcat(buf, "-Oblique");
218 } else if ( f->family == NAME_times )
219 { strcpy(buf, "Times");
220
221 if ( f->style == NAME_bold )
222 strcat(buf, "-Bold");
223 else if ( f->style == NAME_italic )
224 strcat(buf, "-Italic");
225 else /*if ( f->style == NAME_roman )*/
226 strcat(buf, "-Roman");
227 } else if ( f->style == NAME_ansiVar )
228 { strcpy(buf, "Helvetica");
229 } else /* default */
230 { strcpy(buf, "Courier");
231
232 if ( f->style == NAME_bold )
233 strcat(buf, "-Bold");
234 else if ( f->style == NAME_oblique )
235 strcat(buf, "-Oblique");
236 }
237
238 assign(f, postscript_size, getPointsFont(f));
239 assign(f, postscript_font, CtoName(buf));
240
241 succeed;
242 }
243
244
245 /********************************
246 * GET INFO *
247 ********************************/
248
249
250 Int
getWidthFont(FontObj f,CharArray txt)251 getWidthFont(FontObj f, CharArray txt)
252 { if ( isDefault(txt) )
253 txt = (CharArray) NAME_x;
254
255 d_ensure_display(); /* TBD */
256
257 answer(toInt(str_width(&txt->data, 0, txt->data.s_size, f)));
258 }
259
260
261 Int
getAdvanceFont(FontObj f,CharArray txt)262 getAdvanceFont(FontObj f, CharArray txt)
263 { d_ensure_display(); /* TBD */
264
265 return toInt(str_advance(&txt->data, 0, txt->data.s_size, f));
266 }
267
268
269 Int
getExFont(FontObj f)270 getExFont(FontObj f)
271 { if ( isNil(f->ex) )
272 assign(f, ex, toInt(c_width('x', f)));
273
274 answer(f->ex);
275 }
276
277
278 Int
getHeightFont(FontObj f)279 getHeightFont(FontObj f)
280 { d_ensure_display();
281
282 answer(toInt(s_height(f)));
283 }
284
285
286 Int
getAscentFont(FontObj f)287 getAscentFont(FontObj f)
288 { d_ensure_display();
289
290 answer(toInt(s_ascent(f)));
291 }
292
293
294 Int
getDescentFont(FontObj f)295 getDescentFont(FontObj f)
296 { d_ensure_display();
297
298 answer(toInt(s_descent(f)));
299 }
300
301
302 static Size
getSizeFont(FontObj f)303 getSizeFont(FontObj f)
304 { answer(answerObject(ClassSize, getExFont(f), getHeightFont(f), EAV));
305 }
306
307
308 BoolObj
getFixedWidthFont(FontObj f)309 getFixedWidthFont(FontObj f)
310 { if ( isDefault(f->fixed_width) )
311 { getXrefObject(f, CurrentDisplay(NIL));
312
313 if ( c_width('x', f) == c_width('W', f) )
314 assign(f, fixed_width, ON);
315 else
316 assign(f, fixed_width, OFF);
317 }
318
319 answer(f->fixed_width);
320 }
321
322
323 BoolObj
getB16Font(FontObj f)324 getB16Font(FontObj f)
325 { if ( isDefault(f->iswide) )
326 XopenFont(f, CurrentDisplay(NIL));
327
328 answer(f->iswide);
329 }
330
331
332 static status
memberFont(FontObj f,Int chr)333 memberFont(FontObj f, Int chr)
334 { d_ensure_display();
335
336 if ( s_has_char(f, valInt(chr)) )
337 succeed;
338
339 fail;
340 }
341
342
343 static Int
getDefaultCharacterFont(FontObj f)344 getDefaultCharacterFont(FontObj f)
345 { d_ensure_display();
346
347 answer(toInt(s_default_char(f)));
348 }
349
350
351 static Tuple
getDomainFont(FontObj f,Name which)352 getDomainFont(FontObj f, Name which)
353 { int a, z;
354
355 if ( isDefault(which) )
356 which = NAME_x;
357
358 f_domain(f, which, &a, &z);
359 return answerObject(ClassTuple, toInt(a), toInt(z), EAV);
360 }
361
362
363 static Int
getPointsFont(FontObj f)364 getPointsFont(FontObj f)
365 { if ( notDefault(f->points) )
366 answer(f->points);
367
368 answer(getHeightFont(f));
369 }
370
371
372 /*******************************
373 * CLASS DECLARATION *
374 *******************************/
375
376 /* Type declarations */
377
378 static char *T_initialise[] =
379 { "family=name", "style=name", "points=[int]", "x_name=[name]" };
380 static char *T_lookup[] =
381 { "name", "name", "[int]" };
382
383 /* Instance Variables */
384
385 static vardecl var_font[] =
386 { IV(NAME_family, "name", IV_GET,
387 NAME_name, "Family the font belongs to (times, etc.)"),
388 IV(NAME_style, "name", IV_GET,
389 NAME_name, "Style of the font (bold, italic, etc.)"),
390 IV(NAME_points, "[int]", IV_NONE,
391 NAME_name, "Point-size of the font"),
392 IV(NAME_ex, "int*", IV_NONE,
393 NAME_dimension, "Width of the letter `x' in this font"),
394 IV(NAME_xName, "[name]", IV_GET,
395 NAME_x, "Window-system name for the font"),
396 IV(NAME_fixedWidth, "[bool]", IV_NONE,
397 NAME_property, "If @off, font is proportional"),
398 IV(NAME_b16, "[bool]", IV_NONE,
399 NAME_property, "If @on, font is a 16-bit font"),
400 IV(NAME_postscriptFont, "name", IV_BOTH,
401 NAME_postscript, "PostScript-name of the font"),
402 IV(NAME_postscriptSize, "int", IV_BOTH,
403 NAME_postscript, "PostScript point-size of the font")
404 };
405
406 /* Send Methods */
407
408 static senddecl send_font[] =
409 { SM(NAME_initialise, 4, T_initialise, initialiseFont,
410 DEFAULT, "Create from fam, style, points, name"),
411 SM(NAME_member, 1, "char", memberFont,
412 NAME_set, "Test if font defines character"),
413 SM(NAME_Xclose, 1, "display", XcloseFont,
414 NAME_x, "Destroy associated window-system resources"),
415 SM(NAME_Xopen, 1, "display", XopenFont,
416 NAME_x, "Open the associated window-system resources")
417 };
418
419 /* Get Methods */
420
421 static getdecl get_font[] =
422 { GM(NAME_points, 0, "int", NULL, getPointsFont,
423 DEFAULT, "Specified point-size or <-height"),
424 GM(NAME_convert, 1, "font", "name", getConvertFont,
425 NAME_conversion, "Convert logical font-name and @family_style_points"),
426 GM(NAME_ascent, 0, "int", NULL, getAscentFont,
427 NAME_dimension, "Highest point above baseline"),
428 GM(NAME_descent, 0, "int", NULL, getDescentFont,
429 NAME_dimension, "Lowest point below baseline"),
430 GM(NAME_ex, 0, "int", NULL, getExFont,
431 NAME_dimension, "Width of the letter `x'"),
432 GM(NAME_height, 0, "int", NULL, getHeightFont,
433 NAME_dimension, "Height of highest character in font"),
434 GM(NAME_size, 0, "size", NULL, getSizeFont,
435 NAME_dimension, "New size from <-width and <-height"),
436 GM(NAME_width, 1, "int", "[char_array]", getWidthFont,
437 NAME_dimension, "Width of string (default \"x\")"),
438 GM(NAME_advance, 1, "int", "char_array", getAdvanceFont,
439 NAME_dimension, "X-origin advancement of string"),
440 GM(NAME_b16, 0, "bool", NULL, getB16Font,
441 NAME_encoding, "Boolean to indicate font is 16-bits"),
442 GM(NAME_lookup, 3, "font", T_lookup, getLookupFont,
443 NAME_oms, "Lookup in @fonts table"),
444 GM(NAME_defaultCharacter, 0, "char", NULL, getDefaultCharacterFont,
445 NAME_property, "Character painted for non-existing entries"),
446 GM(NAME_domain, 1, "tuple", "[{x,y}]", getDomainFont,
447 NAME_property, "Range of valid characters"),
448 GM(NAME_fixedWidth, 0, "bool", NULL, getFixedWidthFont,
449 NAME_property, "Boolean to indicate font is fixed-width")
450 };
451
452 /* Resources */
453
454 static classvardecl rc_font[] =
455 { RC(NAME_scale, "real", UXWIN("1.0", "1.4"),
456 "Multiplication factor for all fonts")
457 };
458
459 /* Class Declaration */
460
461 static Name font_termnames[] = { NAME_family, NAME_style, NAME_points };
462
463 ClassDecl(font_decls,
464 var_font, send_font, get_font, rc_font,
465 3, font_termnames,
466 "$Rev$");
467
468
469 status
makeClassFont(Class class)470 makeClassFont(Class class)
471 { declareClass(class, &font_decls);
472
473 saveStyleClass(class, NAME_external);
474 cloneStyleClass(class, NAME_none);
475
476 FontTable = globalObject(NAME_fonts, ClassHashTable, toInt(101), EAV);
477
478 succeed;
479 }
480