1 /*  Part of XPCE --- The SWI-Prolog GUI toolkit
2 
3     Author:        Jan Wielemaker and Anjo Anjewierden
4     E-mail:        jan@swi.psy.uva.nl
5     WWW:           http://www.swi.psy.uva.nl/projects/xpce/
6     Copyright (c)  1995-2011, 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 "include.h"
36 
37 #define FONTTABLESIZE	256
38 #define STOCKFMT "GetStockObject(%d)"
39 
40 typedef struct _lname
41 { char *name;
42   int   value;
43 } lname;
44 
45 
46 static lname charset_names[] =
47 { { "ansi",	ANSI_CHARSET },
48   { "oem",	OEM_CHARSET },
49   { "symbol",	SYMBOL_CHARSET },
50 #ifdef UNICODE_CHARSET
51   { "unicode",	UNICODE_CHARSET },
52 #endif
53   { NULL,	0 }
54 };
55 
56 
57 static lname outprecision_names[] =
58 { { "character",OUT_CHARACTER_PRECIS },
59   { "default",	OUT_DEFAULT_PRECIS },
60   { "device",	OUT_DEVICE_PRECIS },
61   { "outline",	OUT_OUTLINE_PRECIS },
62   { "raster",	OUT_RASTER_PRECIS },
63   { "string",	OUT_STRING_PRECIS },
64   { "stroke",	OUT_STROKE_PRECIS },
65   { "tt_only",	OUT_TT_ONLY_PRECIS },
66   { "tt",	OUT_TT_PRECIS },
67   { NULL,	0 }
68 };
69 
70 
71 static lname clipprecision_names[] =
72 { { "character",CLIP_CHARACTER_PRECIS },
73   { "default",	CLIP_DEFAULT_PRECIS },
74   { "stroke",	CLIP_STROKE_PRECIS },
75   { NULL,	0 }
76 };
77 
78 
79 static lname quality_names[] =
80 { { "default",  DEFAULT_QUALITY },
81   { "draft",	DRAFT_QUALITY },
82   { "proof",	PROOF_QUALITY },
83   { NULL,	0 }
84 };
85 
86 
87 static lname pitch_names[] =
88 { { "default",  DEFAULT_PITCH },
89   { "fixed",	FIXED_PITCH },
90   { "variable",	VARIABLE_PITCH },
91   { NULL,	0 }
92 };
93 
94 
95 static lname family_names[] =
96 { { "decorative",  FF_DECORATIVE },
97   { "dontcare",	   FF_DONTCARE },
98   { "modern",	   FF_MODERN },
99   { "roman",	   FF_ROMAN },
100   { "script",	   FF_SCRIPT },
101   { "swiss",	   FF_SWISS },
102   { NULL,	0 }
103 };
104 
105 
106 static int
named_attribute(char * s,lname * names,int mask,BYTE * value)107 named_attribute(char *s, lname *names, int mask, BYTE *value)
108 { char *sc = s;
109 
110   if ( *sc++ != '(' )
111     return -1;
112 
113   for(; names; names++)
114   { char *q = sc;
115     char *r = names->name;
116 
117     while(*r && tolower(*q) == tolower(*r))
118       r++, q++;
119     if ( *r == EOS && *q++ == ')' )
120     { *value &= ~mask;
121       *value |= names->value;
122       return q-s;
123     }
124   }
125 
126   return -1;
127 }
128 
129 
130 static int
string_attribute(char * s,char * string,int len)131 string_attribute(char *s, char *string, int len)
132 { char *q = s;
133   char *r = string;
134 
135   if ( *q++ != '(' )
136     return -1;
137   while(isspace(*q))
138     q++;				/* kill leading blanks */
139   while(*q && *q != ')' && len-- > 0)
140     *r++ = *q++;
141   if ( *q++ == ')' )
142   { while(r>string && isspace(r[-1]))
143       r--;				/* kill trailing blanks */
144 
145     *r = EOS;
146     return q-s;
147   }
148 
149   return -1;
150 }
151 
152 
153 static status
long_attribute(char * s,LONG * val)154 long_attribute(char *s, LONG *val)
155 { char *q = s;
156   LONG rval = 0;
157 
158   if ( *q++ != '(' )
159     return -1;
160   while(isdigit(*q))
161     rval = rval * 10 + *q++ - '0';
162   if ( *q++ == ')' )
163   { *val = rval;
164     return q-s;
165   }
166 
167   return -1;
168 }
169 
170 
171 static status
bool_attribute(char * s,BYTE * val)172 bool_attribute(char *s, BYTE *val)
173 { *val = TRUE;
174 
175   return 0;
176 }
177 
178 
179 static status
parse_font(char * s,LOGFONT * lfont)180 parse_font(char *s, LOGFONT *lfont)
181 { while(*s)
182   { char att[100];
183     int n = -1;
184     char *q;
185 
186     for(q=att; isalpha(*s); *q++ = *s++)
187       ;
188     *q = EOS;
189 
190     if ( stricmp(att, "height") == 0 )
191       n=long_attribute(s, &lfont->lfHeight);
192     else if ( stricmp(att, "width") == 0 )
193       n=long_attribute(s, &lfont->lfWidth);
194     else if ( stricmp(att, "escapement") == 0 )
195       n=long_attribute(s, &lfont->lfEscapement);
196     else if ( stricmp(att, "orientation") == 0 )
197       n=long_attribute(s, &lfont->lfOrientation);
198     else if ( stricmp(att, "weight") == 0 )
199       n=long_attribute(s, &lfont->lfWeight);
200     else if ( stricmp(att, "italic") == 0 )
201       n=bool_attribute(s, &lfont->lfItalic);
202     else if ( stricmp(att, "underline") == 0 )
203       n=bool_attribute(s, &lfont->lfUnderline);
204     else if ( stricmp(att, "strikeout") == 0 )
205       n=bool_attribute(s, &lfont->lfStrikeOut);
206     else if ( stricmp(att, "charset") == 0 )
207       n=named_attribute(s, charset_names, 0xff, &lfont->lfCharSet);
208     else if ( stricmp(att, "outprecision") == 0 )
209       n=named_attribute(s, outprecision_names, 0xff, &lfont->lfOutPrecision);
210     else if ( stricmp(att, "clipprecision") == 0 )
211       n=named_attribute(s, clipprecision_names, 0xff, &lfont->lfClipPrecision);
212     else if ( stricmp(att, "quality") == 0 )
213       n=named_attribute(s, quality_names, 0xff, &lfont->lfQuality);
214     else if ( stricmp(att, "pitch") == 0 )
215       n=named_attribute(s, pitch_names, 0x3, &lfont->lfPitchAndFamily);
216     else if ( stricmp(att, "family") == 0 )
217       n=named_attribute(s, family_names, 0xf8, &lfont->lfPitchAndFamily);
218     else if ( stricmp(att, "face") == 0 )
219       n=string_attribute(s, lfont->lfFaceName, LF_FACESIZE);
220     else
221       Cprintf("Bad font-attribute name: %s\n", att);
222 
223     if ( n < 0 )
224     { Cprintf("Bad value for font-attribute %s\n", att);
225       while( *s && *s != ':' )
226 	s++;
227     } else
228     { DEBUG(NAME_font, Cprintf("att %s: read %d chars\n", att, n));
229       s += n;
230       if ( *s == ':' )
231 	s++;
232     }
233   }
234 
235   succeed;
236 }
237 
238 
239 status
ws_create_font(FontObj f,DisplayObj d)240 ws_create_font(FontObj f, DisplayObj d)
241 { WsFont wsf = alloc(sizeof(ws_font));
242 #ifdef __WINDOWS__
243   int widths[FONTTABLESIZE];
244 #else
245   short widths[FONTTABLESIZE];
246 #endif
247   HDC hdc;
248   HFONT old;
249   int n;
250   TEXTMETRIC tm;
251   int stock;
252 
253   if ( sscanf(strName(f->x_name), STOCKFMT, &stock) == 1 )
254   { wsf->hfont      = GetStockObject(stock);
255     wsf->from_stock = TRUE;
256   } else
257   { LOGFONT lfont;
258     Real  scale  = getClassVariableValueObject(f, NAME_scale);
259     float fscale = (scale ? valReal(scale) : 1.4);
260 
261     memset(&lfont, 0, sizeof(lfont));
262     lfont.lfHeight          = (int)((float) valInt(f->points) * fscale);
263     lfont.lfWeight          = (f->style == NAME_bold ? FW_BOLD : FW_NORMAL);
264     lfont.lfItalic          = ((f->style == NAME_italic ||
265 				f->style == NAME_oblique) ? 1 : 0);
266     lfont.lfPitchAndFamily  = (f->family == NAME_screen  ? FIXED_PITCH
267 							 : DEFAULT_PITCH);
268     lfont.lfPitchAndFamily |= (f->family == NAME_helvetica ? FF_SWISS :
269 			       f->family == NAME_times     ? FF_ROMAN :
270 			       f->family == NAME_screen    ? FF_MODERN :
271 							     FF_DONTCARE);
272 
273     if ( f->family == NAME_symbol )
274       strcpy(lfont.lfFaceName, "symbol");
275 
276     if ( instanceOfObject(f->x_name, ClassCharArray) )
277     { strcpy(lfont.lfFaceName, strName(f->family));
278 
279       parse_font(strName(f->x_name), &lfont);
280     } else
281     { lfont.lfOutPrecision  = OUT_TT_ONLY_PRECIS;
282       lfont.lfQuality	    = PROOF_QUALITY;
283     }
284 
285     if ( !(wsf->hfont = CreateFontIndirect(&lfont)) )
286     { Cprintf("Failed to create logical font; replacing with stock font\n");
287 
288       if ( f->family == NAME_screen )
289       { if ( f->style == NAME_bold )
290 	  stock = SYSTEM_FIXED_FONT;
291 	else
292 	  stock = ANSI_FIXED_FONT;
293       } else
294       { if ( f->style == NAME_bold )
295 	  stock = SYSTEM_FONT;
296 	else
297 	  stock = ANSI_VAR_FONT;
298       }
299 
300       wsf->hfont      = GetStockObject(stock);
301       wsf->from_stock = TRUE;
302     } else
303       wsf->from_stock = FALSE;
304   }
305 
306   wsf->widths     = alloc(FONTTABLESIZE * sizeof(cwidth));
307   assign(f, iswide, OFF);
308 
309   hdc = GetDC(NULL);
310   old = SelectObject(hdc, wsf->hfont);
311   GetCharWidth(hdc, 0, FONTTABLESIZE-1, widths);
312   for(n=0; n<FONTTABLESIZE; n++)
313     wsf->widths[n] = widths[n];
314   GetTextMetrics(hdc, &tm);
315   wsf->ascent  = tm.tmAscent + tm.tmExternalLeading;
316   wsf->descent = tm.tmDescent;
317 /*if ( !(tm.tmPitchAndFamily & TMPF_TRUETYPE) && f->family != NAME_win )
318     Cprintf("%s (%s/%s): not a TrueType font\n",
319 	    pp(f), pp(f->family), pp(f->style));
320 */
321   if ( isDefault(f->x_name) )
322   { char buf[256];
323 
324     if ( GetTextFace(hdc, sizeof(buf), buf) )
325       assign(f, x_name, CtoName(buf));
326   }
327   SelectObject(hdc, old);
328   ReleaseDC(NULL, hdc);
329 
330   if ( wsf->widths['i'] == wsf->widths['w'] )
331     assign(f, fixed_width, ON);
332   else
333     assign(f, fixed_width, OFF);
334 
335   registerXrefObject(f, d, wsf);
336 
337   succeed;
338 }
339 
340 
341 void
ws_destroy_font(FontObj f,DisplayObj d)342 ws_destroy_font(FontObj f, DisplayObj d)
343 { WsFont wsf = (WsFont) getExistingXrefObject(f, d);
344 
345   DEBUG(NAME_font, Cprintf("ws_destroy_font(%s)\n", pp(f)));
346 
347   if ( wsf )
348   { if ( !wsf->from_stock )
349       ZDeleteObject(wsf->hfont);
350     unregisterXrefObject(f, d);
351   }
352 }
353 
354 
355 static struct system_font
356 { char *name;
357   int  id;
358 } window_fonts [] =
359 { { "ansi_fixed",	ANSI_FIXED_FONT },
360   { "ansi_var",		ANSI_VAR_FONT },
361   { "device_default",	DEVICE_DEFAULT_FONT },
362   { "oem_fixed",	OEM_FIXED_FONT },
363   { "system",		SYSTEM_FONT },
364   { "system_fixed",	SYSTEM_FIXED_FONT },
365 
366   { NULL,		0 }
367 };
368 
369 
370 status
ws_system_fonts(DisplayObj d)371 ws_system_fonts(DisplayObj d)
372 { struct system_font *sf;
373 
374   for(sf = window_fonts; sf->name; sf++)
375   { char buf[256];
376 
377     sprintf(buf, STOCKFMT, sf->id);
378 
379     newObject(ClassFont,
380 	      NAME_win, CtoKeyword(sf->name), DEFAULT,
381 	      CtoName(buf), EAV);
382   }
383 
384   succeed;
385 }
386