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/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 <h/kernel.h>
36 #include <fcntl.h>
37 #include <h/interface.h>
38 #include <errno.h>
39 
40 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
41 Thread objects as SWI-Prolog streams. This module  is used by the Prolog
42 interface through pce_open/3. It should be merged with iostream.c, which
43 defines almost the same, providing XPCE with uniform access to a variety
44 of objects.
45 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
46 
47 typedef struct pce_file_handle * PceFileHandle;
48 
49 struct pce_file_handle
50 { long		magic;			/* PCE_IO_MAGIC */
51   Any		object;			/* object `file-i-fied' */
52   long		point;			/* current position */
53   int		flags;			/* general flags field */
54   IOENC		encoding;		/* Stream encoding used */
55   int		my_flags;		/* private flags */
56 };
57 
58 #define		PCE_IO_MAGIC	0x72eb9ace
59 
60 #define		MY_ISSTREAM	0x0001	/* data a a byte-stream */
61 
62 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
63 Open flags recognised:
64 
65 	PCE_RDONLY	Reading only
66 	PCE_WRONLY	Writing only
67 	PCE_RDWR	Reading and writing
68 	PCE_APPEND	Keep appending
69 	PCE_TRUNC	Tuncate object prior to writing
70 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
71 
72 static PceFileHandle *handles;		/* array of handles */
73 static int max_handles=0;		/* # handles allocated */
74 
75 static int
allocFileHandle()76 allocFileHandle()
77 { int handle;
78 
79   for(handle = 0; handle < max_handles; handle++)
80   { if ( handles[handle] == NULL )
81       return handle;
82   }
83 
84   { PceFileHandle *newhandles;
85     int n;
86 
87     if ( max_handles == 0 )
88     { n = 16;
89       newhandles = pceMalloc(sizeof(PceFileHandle) * n);
90     } else
91     { n = max_handles*2;
92       newhandles = pceRealloc(handles, sizeof(PceFileHandle) * n);
93     }
94 
95     if ( newhandles )
96     { int rval = max_handles;
97 
98       memset(&newhandles[max_handles], 0,
99 	     sizeof(PceFileHandle) * (n-max_handles));
100       max_handles = n;
101       handles = newhandles;
102 
103       return rval;
104     }
105 
106     errno = ENOMEM;
107     return -1;
108   }
109 }
110 
111 
112 static int
pceOpen_nolock(Any obj,int flags,void * encoding)113 pceOpen_nolock(Any obj, int flags, void *encoding)
114 { int handle = allocFileHandle();
115   PceFileHandle h;
116 
117   if ( handle < 0 )
118     return handle;
119 
120   if ( !isProperObject(obj) )
121   { errno = EINVAL;
122     return -1;
123   }
124 
125   if ( flags & PCE_WRONLY )
126   { if ( !hasSendMethodObject(obj, NAME_writeAsFile) )
127     { errno = EACCES;
128       return -1;
129     }
130 
131     if ( flags & PCE_TRUNC )
132     { if ( !hasSendMethodObject(obj, NAME_truncateAsFile) ||
133 	   !send(obj, NAME_truncateAsFile, EAV) )
134       { errno = EACCES;
135 	return -1;
136       }
137     }
138   }
139   if ( flags & PCE_RDONLY )
140   { if ( !hasGetMethodObject(obj, NAME_readAsFile) )
141     { errno = EACCES;
142       return -1;
143     }
144   }
145 
146   h = alloc(sizeof(struct pce_file_handle));
147   h->object = obj;
148   addRefObj(obj);			/* so existence check is safe */
149   h->flags = flags;
150   h->point = 0L;
151   h->my_flags = 0;
152 
153   if ( instanceOfObject(obj, ClassStream) )
154   { h->my_flags |= MY_ISSTREAM;
155     h->encoding = ENC_OCTET;
156   } else
157   { h->encoding = ENC_WCHAR;
158   }
159 
160   handles[handle] = h;
161   h->magic = PCE_IO_MAGIC;
162 
163   if ( encoding )
164   { IOENC *ep = encoding;
165 
166     *ep = h->encoding;
167   }
168 
169   return handle;
170 }
171 
172 int
pceOpen(Any obj,int flags,void * encoding)173 pceOpen(Any obj, int flags, void *encoding)
174 { int rc;
175 
176   pceMTLock(LOCK_PCE);
177   rc = pceOpen_nolock(obj, flags, encoding);
178   pceMTUnlock(LOCK_PCE);
179 
180   return rc;
181 }
182 
183 
184 static int
pceClose_nolock(int handle)185 pceClose_nolock(int handle)
186 { PceFileHandle h;
187 
188   if ( handle >= 0 && handle < max_handles &&
189        (h = handles[handle]) )
190   { delRefObject(NIL, h->object);	/* handles deferred unalloc() */
191     h->magic = 0;
192     unalloc(sizeof(struct pce_file_handle), h);
193     handles[handle] = NULL;
194 
195     return 0;
196   }
197 
198   errno = EBADF;
199   return -1;
200 }
201 
202 
203 int
pceClose(int handle)204 pceClose(int handle)
205 { int rc;
206 
207   pceMTLock(LOCK_PCE);
208   rc = pceClose_nolock(handle);
209   pceMTUnlock(LOCK_PCE);
210 
211   return rc;
212 }
213 
214 
215 static PceFileHandle
findHandle(int handle)216 findHandle(int handle)
217 { PceFileHandle h;
218 
219   if ( handle >= 0 &&
220        handle < max_handles &&
221        (h = handles[handle]) &&
222        h->magic == PCE_IO_MAGIC )
223     return h;
224 
225   errno = EBADF;
226   return NULL;
227 }
228 
229 
230 
231 static ssize_t
pceWrite_nolock(int handle,const char * buf,size_t size)232 pceWrite_nolock(int handle, const char *buf, size_t size)
233 { PceFileHandle h;
234 
235   if ( !(h=findHandle(handle)) )
236     return -1;
237 
238   if ( h->flags & (PCE_RDWR|PCE_WRONLY) )
239   { string s;
240     CharArray ca;
241     status rval;
242     Int where = (h->flags & PCE_APPEND ? (Int) DEFAULT : toInt(h->point));
243     const wchar_t *wbuf = (const wchar_t*)buf;
244     const wchar_t *end = (const wchar_t*)&buf[size];
245     const wchar_t *f;
246 
247     if ( isFreedObj(h->object) )
248     { errno = EIO;
249       return -1;
250     }
251 
252     if ( (h->my_flags & MY_ISSTREAM) )
253     { str_set_n_ascii(&s, size, (char*)buf);
254     } else
255     { assert(size%sizeof(wchar_t) == 0);
256 
257       for(f=wbuf; f<end; f++)
258       { if ( *f > 0xff )
259 	  break;
260       }
261 
262       if ( f == end )
263       { charA *asc = alloca(size);
264 	charA *t = asc;
265 
266 	for(f=wbuf; f<end; )
267 	  *t++ = (charA)*f++;
268 
269 	str_set_n_ascii(&s, size/sizeof(wchar_t), (char*)asc);
270       } else
271       { str_set_n_wchar(&s, size/sizeof(wchar_t), (wchar_t*)wbuf);
272       }
273     }
274 
275     ca = StringToScratchCharArray(&s);
276 
277     if ( (rval = send(h->object, NAME_writeAsFile, where, ca, EAV)) )
278       h->point += (long)size/sizeof(wchar_t);
279     doneScratchCharArray(ca);
280 
281     if ( rval )
282       return size;
283 
284     errno = EIO;
285     return -1;
286   } else
287   { errno = EBADF;
288     return -1;
289   }
290 }
291 
292 
293 ssize_t
pceWrite(int handle,const char * buf,size_t size)294 pceWrite(int handle, const char *buf, size_t size)
295 { ssize_t rc;
296 
297   pceMTLock(LOCK_PCE);
298   rc = pceWrite_nolock(handle, buf, size);
299   pceMTUnlock(LOCK_PCE);
300 
301   return rc;
302 }
303 
304 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
305 Note: pos is measured  in  bytes.  If   we  use  wchar  encoding we must
306 compensate for this.
307 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
308 
309 static long
pceSeek_nolock(int handle,long offset,int whence)310 pceSeek_nolock(int handle, long offset, int whence)
311 { PceFileHandle h;
312 
313   offset /= sizeof(wchar_t);
314 
315   if ( (h=findHandle(handle)) )
316   { Int size;
317 
318     if ( isFreedObj(h->object) )
319     { errno = EIO;
320       return -1;
321     }
322 
323     switch(whence)
324     { case PCE_SEEK_SET:
325 	h->point = offset;
326         break;
327       case PCE_SEEK_CUR:
328         h->point += offset;
329         break;
330       case PCE_SEEK_END:
331       { if ( hasGetMethodObject(h->object, NAME_sizeAsFile) &&
332 	     (size = get(h->object, NAME_sizeAsFile, EAV)) )
333 	{ h->point = valInt(size) - offset;
334 	  break;
335 	} else
336 	{ errno = EPIPE;		/* better idea? */
337 	  return -1;
338 	}
339       }
340       default:
341       { errno = EINVAL;
342 	return -1;
343       }
344     }
345     return h->point * sizeof(wchar_t);
346   } else
347   { errno = EBADF;
348     return -1;
349   }
350 }
351 
352 
353 long
pceSeek(int handle,long offset,int whence)354 pceSeek(int handle, long offset, int whence)
355 { long rc;
356 
357   pceMTLock(LOCK_PCE);
358   rc = pceSeek_nolock(handle, offset, whence);
359   pceMTUnlock(LOCK_PCE);
360 
361   return rc;
362 }
363 
364 
365 /* see also Sread_object() */
366 
367 static ssize_t
pceRead_nolock(int handle,char * buf,size_t size)368 pceRead_nolock(int handle, char *buf, size_t size)
369 { PceFileHandle h;
370 
371   if ( !(h=findHandle(handle)) )
372     return -1;
373 
374   if ( h->flags & (PCE_RDWR|PCE_RDONLY) )
375   { Any argv[2];
376     CharArray sub;
377     int chread;
378 
379     if ( isFreedObj(h->object) )
380     { errno = EIO;
381       return -1;
382     }
383 
384     argv[0] = toInt(h->point);
385     argv[1] = toInt(size/sizeof(wchar_t));
386 
387     if ( (sub = getv(h->object, NAME_readAsFile, 2, argv)) &&
388 	 instanceOfObject(sub, ClassCharArray) )
389     { PceString s = &sub->data;
390 
391       assert(s->s_size <= size/sizeof(wchar_t));
392 
393       if ( isstrA(s) )
394       { charW *dest = (charW*)buf;
395 	const charA *f = s->s_textA;
396 	const charA *e = &f[s->s_size];
397 
398 	while(f<e)
399 	  *dest++ = *f++;
400       } else
401       { memcpy(buf, s->s_textW, s->s_size*sizeof(charW));
402       }
403 
404       chread = s->s_size * sizeof(wchar_t);
405       h->point += s->s_size;
406     } else
407     { errno = EIO;
408       chread = -1;
409     }
410 
411     return chread;
412   } else
413   { errno = EBADF;
414     return -1;
415   }
416 }
417 
418 
419 ssize_t
pceRead(int handle,char * buf,size_t size)420 pceRead(int handle, char *buf, size_t size)
421 { ssize_t rc;
422 
423   pceMTLock(LOCK_PCE);
424   rc = pceRead_nolock(handle, buf, size);
425   pceMTUnlock(LOCK_PCE);
426 
427   return rc;
428 }
429 
430 
431 int
pceControl_nolock(int handle,int cmd,void * closure)432 pceControl_nolock(int handle, int cmd, void *closure)
433 { PceFileHandle h;
434 
435   if ( !(h=findHandle(handle)) )
436     return -1;
437 
438   switch(cmd)
439   { case PCE_SETENCODING:
440       if ( (h->my_flags & MY_ISSTREAM) )
441 	return 0;
442   }
443 
444   errno = EPERM;
445   return -1;
446 }
447 
448 int
pceControl(int handle,int cmd,void * closure)449 pceControl(int handle, int cmd, void *closure)
450 { int rc;
451 
452   pceMTLock(LOCK_PCE);
453   rc = pceControl_nolock(handle, cmd, closure);
454   pceMTUnlock(LOCK_PCE);
455 
456   return rc;
457 }
458 
459 
460 const char *
pceOsError()461 pceOsError()
462 { return strName(getOsErrorPce(PCE));
463 }
464