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-2013, 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 #include <h/interface.h>
37 #include <h/unix.h>
38 
39 /* Allow compilation with old SDKs, also allow working with old OS
40    versions that do not provide the functions in user32.dll.
41 */
42 
43 #define COMPILE_MULTIMON_STUBS 1
44 #include "multimon.h"
45 
46 void
ws_flush_display(DisplayObj d)47 ws_flush_display(DisplayObj d)
48 { ws_synchronise_display(d);
49 }
50 
51 
52 void
ws_synchronise_display(DisplayObj d)53 ws_synchronise_display(DisplayObj d)
54 { MSG msg;
55 
56   while ( PeekMessage(&msg, NULL, 0, 0, PM_REMOVE) )
57   { TranslateMessage(&msg);
58     DispatchMessage(&msg);
59   }
60 }
61 
62 
63 void
ws_bell_display(DisplayObj d,int volume)64 ws_bell_display(DisplayObj d, int volume)
65 { MessageBeep(MB_ICONEXCLAMATION);
66 }
67 
68 
69 void
ws_get_size_display(DisplayObj d,int * w,int * h)70 ws_get_size_display(DisplayObj d, int *w, int *h)
71 { HDC  hdc = GetDC(NULL);
72 
73 #if 0
74   *w = GetDeviceCaps(hdc, HORZRES);
75   *h = GetDeviceCaps(hdc, VERTRES);
76 #else
77   *w = GetSystemMetrics(SM_CXVIRTUALSCREEN);
78   *h = GetSystemMetrics(SM_CYVIRTUALSCREEN);
79 #endif
80 
81   ReleaseDC(NULL, hdc);
82 }
83 
84 
85 Name
ws_get_visual_type_display(DisplayObj d)86 ws_get_visual_type_display(DisplayObj d)
87 { int depth = ws_depth_display(d);
88 
89   if ( depth == 1 )
90     return NAME_monochrome;
91   else if ( depth <= 8 )		/* test for colourmap? */
92     return NAME_pseudoColour;
93   else
94     return NAME_trueColour;
95 }
96 
97 
98 int
ws_depth_display(DisplayObj d)99 ws_depth_display(DisplayObj d)
100 { HDC  hdc = GetDC(NULL);
101   int depth = GetDeviceCaps(hdc, BITSPIXEL);
102   ReleaseDC(NULL, hdc);
103 
104   return depth;
105 }
106 
107 
108 int
ws_resolution_display(DisplayObj d,int * rx,int * ry)109 ws_resolution_display(DisplayObj d, int *rx, int *ry)
110 { HDC hdc = GetDC(NULL);
111 
112   *rx = GetDeviceCaps(hdc, LOGPIXELSX);
113   *ry = GetDeviceCaps(hdc, LOGPIXELSY);
114 
115   ReleaseDC(NULL, hdc);
116 
117   succeed;
118 }
119 
120 
121 void
ws_activate_screen_saver(DisplayObj d)122 ws_activate_screen_saver(DisplayObj d)
123 {
124 }
125 
126 
127 void
ws_deactivate_screen_saver(DisplayObj d)128 ws_deactivate_screen_saver(DisplayObj d)
129 {
130 }
131 
132 
133 void
ws_init_display(DisplayObj d)134 ws_init_display(DisplayObj d)
135 {
136 }
137 
138 
139 status
ws_legal_display_name(char * s)140 ws_legal_display_name(char *s)
141 { succeed;
142 }
143 
144 
145 status
ws_opened_display(DisplayObj d)146 ws_opened_display(DisplayObj d)
147 { if ( d->ws_ref )
148     succeed;
149 
150   fail;
151 }
152 
153 
154 void
ws_open_display(DisplayObj d)155 ws_open_display(DisplayObj d)
156 { d->ws_ref = (WsRef) 1;	/* just flag; nothing to do yet */
157 
158   if ( isDefault(d->colour_map) )
159   { if ( ws_has_colourmap(d) )
160     { int depth = ws_depth_display(d);
161 
162       if ( depth == 8 )
163       { send(d, NAME_colourMap,
164 	     newObject(ClassColourMap, CtoName("colour_cube_216"), EAV), EAV);
165       }
166     } else
167       send(d, NAME_colourMap, NIL, EAV);
168   }
169 
170   ws_init_loc_still_timer();
171 }
172 
173 
174 void
ws_quit_display(DisplayObj d)175 ws_quit_display(DisplayObj d)
176 { exitDraw(0);
177 }
178 
179 
180 static BOOL CALLBACK
next_monitor(HMONITOR m,HDC hdc,LPRECT rect,LPARAM closure)181 next_monitor(HMONITOR m, HDC hdc, LPRECT rect, LPARAM closure)
182 { DisplayObj d = (DisplayObj)closure;
183   MONITORINFOEX info;
184   Any name;
185   Monitor mon;
186 
187   memset(&info, 0, sizeof(info));
188   info.cbSize = sizeof(info);
189   if ( GetMonitorInfo(m, (MONITORINFO*)&info) )
190   { name = CtoName(info.szDevice);
191   } else
192   { name = d->monitors->size;
193   }
194 
195   appendChain(d->monitors,
196 	      mon=newObject(ClassMonitor,
197 			    name,
198 			    newObject(ClassArea,
199 				      toInt(rect->left),
200 				      toInt(rect->top),
201 				      toInt(rect->right - rect->left),
202 				      toInt(rect->bottom - rect->top),
203 				      EAV),
204 			    EAV));
205   if ( isName(name) )
206   { if ( info.dwFlags & MONITORINFOF_PRIMARY )
207       assign(mon, primary, ON);
208     assign(mon, work_area,
209 	   newObject(ClassArea,
210 		     toInt(info.rcWork.left),
211 		     toInt(info.rcWork.top),
212 		     toInt(info.rcWork.right - info.rcWork.left),
213 		     toInt(info.rcWork.bottom - info.rcWork.top),
214 		     EAV));
215   }
216 
217   return TRUE;
218 }
219 
220 
221 status
ws_init_monitors_display(DisplayObj d)222 ws_init_monitors_display(DisplayObj d)
223 { assign(d, monitors, newObject(ClassChain, EAV));
224 
225   EnumDisplayMonitors(NULL, NULL, next_monitor, (LPARAM)d);
226 
227   succeed;
228 }
229 
230 
231 		 /*******************************
232 		 *	  MOUSE TRACKING	*
233 		 *******************************/
234 
235 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
236 The %@^%#@& MS-Windows system does  not   tell  the application when the
237 mouse enters/leaves some window.  News articles   and many mails later I
238 was hardly any further.  Anyway, the following appears to work:
239 
240 Use SetWindowsHookEx() to register a WH_MOUSE hook.  When the hwnd field
241 of the MOUSEHOOKSTRUCT changes, SendMessage()   a  user-defined event to
242 the window left and entered.  Now, if you do that in the app itself, you
243 will not see any result if the mouse leaves towards another application.
244 
245 Therefore we first try to load the pcewh.dll module which does the same,
246 but in a dll, so it can do the   job system-wide.  If this fails we will
247 do the job locally, which in any case is better than not at all.
248 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
249 
250 static HWND current_window;
251 
252 void
PceWhDeleteWindow(HWND win)253 PceWhDeleteWindow(HWND win)
254 { if ( win == current_window )
255     current_window = 0;
256 }
257 
258 
259 static void
send_message(HWND win,UINT msg,WPARAM wParam,LPARAM lParam)260 send_message(HWND win, UINT msg, WPARAM wParam, LPARAM lParam)
261 { DWORD owner = GetWindowThreadProcessId(win, NULL);
262 
263   if ( owner == GetCurrentThreadId() )
264   { SendMessage(win, msg, wParam, lParam);
265   } else
266   { PostMessage(win, msg, wParam, lParam);
267   }
268 }
269 
270 
271 void
PceEventInWindow(HWND win)272 PceEventInWindow(HWND win)
273 { if ( win != current_window )
274   { if ( current_window )
275     { DEBUG(NAME_areaEnter,
276 	    Cprintf("Posting exit to %s\n",
277 		    pp(getObjectFromHWND(current_window))));
278       send_message(current_window, WM_WINEXIT, 0, 0L);
279     }
280     if ( win )
281     { DEBUG(NAME_areaEnter,
282 	    Cprintf("Posting enter to %s\n",
283 		    pp(getObjectFromHWND(win))));
284       send_message(win, WM_WINENTER, 0, 0L);
285     }
286 
287     current_window = win;
288   }
289 }
290 
291 
292 static void
init_area_enter_exit_handling(DisplayObj d)293 init_area_enter_exit_handling(DisplayObj d)
294 {
295 }
296 
297 
298 status
ws_init_graphics_display(DisplayObj d)299 ws_init_graphics_display(DisplayObj d)
300 { initDraw();
301 
302   init_area_enter_exit_handling(d);
303 
304   succeed;
305 }
306 
307 
308 void
ws_foreground_display(DisplayObj d,Colour c)309 ws_foreground_display(DisplayObj d, Colour c)
310 {
311 }
312 
313 
314 void
ws_background_display(DisplayObj d,Colour c)315 ws_background_display(DisplayObj d, Colour c)
316 {
317 }
318 
319 
320 void
ws_draw_in_display(DisplayObj d,Graphical gr,BoolObj invert,BoolObj subtoo)321 ws_draw_in_display(DisplayObj d, Graphical gr, BoolObj invert, BoolObj subtoo)
322 { d_screen(d);
323   if ( invert == ON ) r_invert_mode(ON);
324   if ( subtoo == ON ) r_subwindow_mode(ON);
325   RedrawArea(gr, gr->area);
326   r_invert_mode(OFF);
327   r_subwindow_mode(OFF);
328   d_done();
329 }
330 
331 
332 void
ws_grab_server(DisplayObj d)333 ws_grab_server(DisplayObj d)
334 {
335 }
336 
337 
338 void
ws_ungrab_server(DisplayObj d)339 ws_ungrab_server(DisplayObj d)
340 {
341 }
342 
343 
344 Int
ws_display_connection_number(DisplayObj d)345 ws_display_connection_number(DisplayObj d)
346 { fail;
347 }
348 
349 
350 status
ws_events_queued_display(DisplayObj d)351 ws_events_queued_display(DisplayObj d)
352 { return GetInputState() ? SUCCEED : FAIL;
353 }
354 
355 
356 status
ws_pointer_location_display(DisplayObj d,int * x,int * y)357 ws_pointer_location_display(DisplayObj d, int *x, int *y)
358 { POINT pt;
359 
360   if ( GetCursorPos(&pt) )
361   { *x = (int)pt.x;
362     *y = (int)pt.y;
363 
364     succeed;
365   }
366 
367   fail;
368 }
369 
370 
371 		 /*******************************
372 		 *     SELECTION HANDLING	*
373 		 *******************************/
374 
375 #define CLIPBOARDWIN	PceHiddenWindow()
376 
377 static HGLOBAL
ws_string_to_global_mem(PceString s)378 ws_string_to_global_mem(PceString s)
379 { int size  = s->s_size;
380   int extra = str_count_chr(s, 0, s->s_size, '\n');
381   HGLOBAL mem;
382   wchar_t *data;
383   int i;
384 
385   if ( !(mem = GlobalAlloc(GMEM_MOVEABLE, (size+extra+1)*sizeof(wchar_t))) )
386   { Cprintf("Cannot allocate\n");
387     return 0;
388   }
389 
390   data = GlobalLock(mem);
391 
392   if ( isstrA(s) )
393   { charA *q;
394 
395     for(q=s->s_textA,i=0; i<size; i++)
396     { if ( *q == '\n' )
397 	*data++ = '\r';
398       *data++ = *q++;
399     }
400     *data = EOS;
401   } else
402   { charW *q;
403 
404     for(q=s->s_textW,i=0; i<size; i++)
405     { if ( *q == '\n' )
406 	*data++ = '\r';
407       *data++ = *q++;
408     }
409     *data = EOS;
410   }
411 
412   GlobalUnlock(mem);
413 
414   return mem;
415 }
416 
417 
418 status
ws_set_cutbuffer(DisplayObj d,int n,PceString s)419 ws_set_cutbuffer(DisplayObj d, int n, PceString s)
420 { if ( n == 0 )
421   { HGLOBAL mem = ws_string_to_global_mem(s);
422 
423     OpenClipboard(PceHiddenWindow());
424     EmptyClipboard();
425     SetClipboardData(CF_UNICODETEXT, mem);
426     CloseClipboard();
427 
428     succeed;
429   }
430 
431   Cprintf("Cannot access cut-buffers other than 0\n");
432   fail;
433 }
434 
435 
436 static Any
get_clipboard_data(DisplayObj d,Name type)437 get_clipboard_data(DisplayObj d, Name type)
438 { HGLOBAL mem;
439   HENHMETAFILE hmf;
440   Any rval = FAIL;
441 
442   OpenClipboard(CLIPBOARDWIN);
443   if ( type != NAME_winMetafile && (mem = GetClipboardData(CF_UNICODETEXT)) )
444   { wchar_t *data = GlobalLock(mem);
445     wchar_t *copy, *q;
446 
447     q = copy = pceMalloc((wcslen(data)+1)*sizeof(wchar_t));
448 
449     for(; *data; data++)
450     { if ( *data == '\r' && data[1] == '\n' )
451       { data++;
452 	*q++ = '\n';
453       } else
454 	*q++ = *data;
455     }
456     *q = EOS;
457     rval = WCToString(copy, q-copy);
458     pceFree(copy);
459     GlobalUnlock(mem);
460   } else if ( type != NAME_winMetafile && (mem = GetClipboardData(CF_TEXT)) )
461   { char far *data = GlobalLock(mem);
462     char *copy, *q;
463 
464     q = copy = pceMalloc(strlen(data));
465 
466     for(; *data; data++)
467     { if ( *data == '\r' && data[1] == '\n' )
468       { data++;
469 	*q++ = '\n';
470       } else
471 	*q++ = *data;
472     }
473     *q = EOS;
474     rval = CtoString(copy);
475     pceFree(copy);
476     GlobalUnlock(mem);
477   } else if ( type != NAME_text && (hmf = GetClipboardData(CF_ENHMETAFILE)) )
478   { HENHMETAFILE copy = CopyEnhMetaFile(hmf, NULL);
479     if ( !copy )
480     { errorPce(d, NAME_winMetafile, CtoName("CopyEnhMetaFile"), APIError());
481       fail;
482     }
483 
484     rval = CtoWinMetafile(copy);
485     DeleteEnhMetaFile(hmf);
486   }
487   CloseClipboard();
488 
489   return rval;
490 }
491 
492 
493 StringObj
ws_get_cutbuffer(DisplayObj d,int n)494 ws_get_cutbuffer(DisplayObj d, int n)
495 { if ( n == 0 )
496     return get_clipboard_data(d, NAME_text); /* DEFAULT? */
497 
498   Cprintf("Cannot access cut-buffers other than 0\n");
499   fail;
500 }
501 
502 
503 unsigned long
ws_get_selection_timeout(void)504 ws_get_selection_timeout(void)
505 { return 0L;
506 }
507 
508 
509 void
ws_set_selection_timeout(unsigned long time)510 ws_set_selection_timeout(unsigned long time)
511 {
512 }
513 
514 
515 Any
ws_get_selection(DisplayObj d,Name which,Name target)516 ws_get_selection(DisplayObj d, Name which, Name target)
517 { return get_clipboard_data(d, target);
518 }
519 
520 
521 void
ws_renderall(void)522 ws_renderall(void)
523 { HWND hwnd = CLIPBOARDWIN;
524 
525   OpenClipboard(hwnd);
526   EmptyClipboard();
527   CloseClipboard();
528 }
529 
530 
531 void
ws_disown_selection(DisplayObj d,Name selection)532 ws_disown_selection(DisplayObj d, Name selection)
533 { ws_renderall();
534 }
535 
536 
537 int
ws_provide_selection(int format)538 ws_provide_selection(int format)
539 { DisplayObj d = CurrentDisplay(NIL);
540   Hyper h;
541   Function msg;
542   Name which     = NAME_primary;
543   Name hypername = getAppendName(which, NAME_selectionOwner);
544   Name type;
545 
546   if ( d && notNil(d) &&
547        (h    = getFindHyperObject(d, hypername, DEFAULT)) &&
548        (type = getAttributeObject(h, NAME_type)) &&
549        (msg  = getAttributeObject(h, NAME_convertFunction)) &&
550        (msg  = checkType(msg, TypeFunction, NIL)) )
551   { Any val;
552 
553     DEBUG(NAME_selection, Cprintf("Provide %s selection of type %s\n",
554 				  pp(which), pp(type)));
555 
556     if ( !(val = getForwardReceiverFunction(msg, h->to, which, type, EAV)) )
557       return FALSE;
558 
559     DEBUG(NAME_selection, Cprintf("Got %s\n", pp(val)));
560 
561     if ( type == NAME_text )
562     { CharArray ca = checkType(val, TypeCharArray, NIL);
563 
564       if ( ca )
565       { PceString s = &ca->data;
566       	HGLOBAL mem = ws_string_to_global_mem(s);
567 
568 	if ( mem )
569 	  SetClipboardData(CF_UNICODETEXT, mem);
570 
571 	return TRUE;
572       }
573     } else if ( type == NAME_emf || type == NAME_wmf )
574     { Any mf = checkType(val, nameToType(NAME_winMetafile), NIL);
575 
576       if ( mf )
577       { DEBUG(NAME_selection, Cprintf("Providing win_metafile\n"));
578 	return ws_on_clipboard_metafile(mf, type);
579       }
580     } else
581       return errorPce(d, NAME_noSelectionType, type);
582   }
583 
584   return FALSE;
585 }
586 
587 
588 status
ws_own_selection(DisplayObj d,Name selection,Name type)589 ws_own_selection(DisplayObj d, Name selection, Name type)
590 { HWND hwnd = CLIPBOARDWIN;
591   UINT format;
592 
593   if ( type == NAME_emf )
594     format = CF_ENHMETAFILE;
595   else if ( type == NAME_wmf )
596     format = CF_METAFILEPICT;
597   else if ( type == NAME_text)
598     format = CF_UNICODETEXT;
599   else
600     return errorPce(d, NAME_noSelectionType, type);
601 
602   DEBUG(NAME_selection, Cprintf("%s becomes owner of %selection, type %s\n",
603 				pp(d), pp(selection), pp(type)));
604 
605   OpenClipboard(hwnd);
606   EmptyClipboard();
607   SetClipboardData(format, NULL);
608   CloseClipboard();
609 
610   succeed;
611 }
612 
613 
614 Name
ws_window_manager(DisplayObj d)615 ws_window_manager(DisplayObj d)
616 { answer(CtoName("windows"));
617 }
618 
619 
620 void
ws_synchronous(DisplayObj d)621 ws_synchronous(DisplayObj d)
622 {
623 }
624 
625 
626 void
ws_asynchronous(DisplayObj d)627 ws_asynchronous(DisplayObj d)
628 {
629 }
630 
631 
632 status
ws_postscript_display(DisplayObj d,int iscolor)633 ws_postscript_display(DisplayObj d, int iscolor)
634 { int w = valInt(getWidthDisplay(d));
635   int h = valInt(getHeightDisplay(d));
636   HDC hdc = GetDC(NULL);
637   int depth = GetDeviceCaps(hdc, BITSPIXEL);
638 
639   switch(depth)
640   { case 1:
641       break;
642     case 2:
643     case 4:
644     case 8:				/* colour-mapped */
645     case 16:
646       depth = 4;			/* low-res true-color */
647     case 24:
648     case 32:
649       depth = 8;			/* high-res true color */
650   }
651 
652   ps_output("0 0 ~D ~D ~D ~N\n", w, h,
653 	    depth, iscolor ? NAME_rgbimage : NAME_greymap);
654   postscriptDC(hdc, 0, 0, w, h, depth, iscolor);
655   ps_output("\n");
656 
657   succeed;
658 }
659 
660 
661 Image
ws_grab_image_display(DisplayObj d,int x,int y,int width,int height)662 ws_grab_image_display(DisplayObj d, int x, int y, int width, int height)
663 { HDC hdc = GetDC(NULL);
664   RECT rect;
665   Image image;
666   int w, h;
667   HBITMAP obm, bm;
668   HDC hdcimg;
669   Size size = getSizeDisplay(d);
670 
671   rect.left   = x;
672   rect.top    = y;
673   rect.right  = x + width;
674   rect.bottom = y + height;
675   if ( rect.left < 0 ) rect.left = 0;
676   if ( rect.top < 0 )  rect.top  = 0;
677   if ( rect.bottom > valInt(size->h) ) rect.bottom = valInt(size->h);
678   if ( rect.right >  valInt(size->w) ) rect.right  = valInt(size->w);
679 
680   w = rect.right - rect.left;
681   h = rect.bottom - rect.top;
682 
683   image = answerObject(ClassImage, NIL,
684 		       toInt(w), toInt(h), NAME_pixmap, EAV);
685   assign(image, display, d);
686   bm = ZCreateCompatibleBitmap(hdc, w, h);
687   hdcimg = CreateCompatibleDC(hdc);
688   obm = SelectObject(hdcimg, bm);
689 
690   BitBlt(hdcimg, 0, 0, w, h, hdc, rect.left, rect.top, SRCCOPY);
691 
692   SelectObject(hdcimg, obm);
693   ZDeleteObject(hdcimg);
694   ReleaseDC(NULL, hdc);
695 
696   registerXrefObject(image, image->display, (void *) bm);
697 
698   return image;
699 }
700