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)  1999-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 <h/unix.h>
37 #include <errno.h>
38 
39 		 /*******************************
40 		 *      OBJECT --> IOSTREAM	*
41 		 *******************************/
42 
43 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
44 Reading and writing to objects is  done   using  the `wchar' encoding of
45 streams to fully support international character   sets. To simplify the
46 interface we will translate the size of   the read and write requests to
47 n/sizeof(wchar_t) and do the translation to/from the buffer here.
48 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
49 
50 typedef struct
51 { Any	object;				/* The client (opened) object */
52   long	point;				/* Current location */
53   IOENC encoding;			/* used encoding */
54 } open_object, *OpenObject;
55 
56 
57 static ssize_t
Sread_object(void * handle,char * buf,size_t size)58 Sread_object(void *handle, char *buf, size_t size)
59 { OpenObject h = handle;
60   Any argv[2];
61   CharArray sub;
62   int chread;
63   size_t advance;
64 
65   if ( isFreedObj(h->object) )
66   { errno = EIO;
67     return -1;
68   }
69 
70   if ( h->encoding == ENC_WCHAR )
71   { advance = size/sizeof(wchar_t);
72   } else if ( h->encoding == ENC_OCTET )
73   { advance = size;
74   } else
75   { assert(0);
76     errno = EIO;
77     return -1;
78   }
79 
80   argv[0] = toInt(h->point);
81   argv[1] = toInt(advance);
82 
83   if ( (sub = getv(h->object, NAME_readAsFile, 2, argv)) &&
84        instanceOfObject(sub, ClassCharArray) )
85   { PceString s = &sub->data;
86 
87     assert(s->s_size <= advance);
88 
89     if ( h->encoding == ENC_WCHAR )
90     { if ( isstrA(s) )
91       { charW *dest = (charW*)buf;
92 	const charA *f = s->s_textA;
93 	const charA *e = &f[s->s_size];
94 
95 	while(f<e)
96 	  *dest++ = *f++;
97       } else
98       { memcpy(buf, s->s_textW, s->s_size*sizeof(charW));
99       }
100       chread = s->s_size * sizeof(wchar_t);
101     } else
102     { if ( isstrA(s) )
103       { memcpy(buf, s->s_textA, s->s_size);
104       } else
105       { errno = EIO;
106 	chread = -1;
107       }
108       chread = s->s_size;
109     }
110 
111     h->point += s->s_size;
112   } else
113   { errno = EIO;
114     chread = -1;
115   }
116 
117   return chread;
118 }
119 
120 
121 static ssize_t
Swrite_object(void * handle,char * buf,size_t size)122 Swrite_object(void *handle, char *buf, size_t size)
123 { OpenObject h = handle;
124   string s;
125   CharArray ca;
126   status rval;
127   Int where = toInt(h->point);
128   size_t advance;
129 
130   if ( isFreedObj(h->object) )
131   { errno = EIO;
132     return -1;
133   }
134 
135   if ( h->encoding == ENC_WCHAR )
136   { const wchar_t *wbuf = (const wchar_t*)buf;
137     const wchar_t *end = (const wchar_t*)&buf[size];
138     const wchar_t *f;
139 
140     assert(size%sizeof(wchar_t) == 0);
141     advance = size/sizeof(wchar_t);
142 
143     for(f=wbuf; f<end; f++)
144     { if ( *f > 0xff )
145 	break;
146     }
147 
148     if ( f == end )
149     { charA *asc = alloca(size);
150       charA *t = asc;
151 
152       for(f=wbuf; f<end; )
153 	*t++ = (charA)*f++;
154 
155       str_set_n_ascii(&s, advance, (char*)asc);
156     } else
157     { str_set_n_wchar(&s, advance, (wchar_t*)wbuf);
158     }
159   } else if ( h->encoding == ENC_OCTET )
160   { advance = size;
161     str_set_n_ascii(&s, size, buf);
162   } else
163   { assert(0);
164     errno = EIO;
165     return -1;
166   }
167 
168   ca = StringToScratchCharArray(&s);
169 
170   if ( (rval = send(h->object, NAME_writeAsFile, where, ca, EAV)) )
171     h->point += (long)advance;
172   doneScratchCharArray(ca);
173 
174   if ( rval )
175     return size;
176 
177   errno = EIO;
178   return -1;
179 }
180 
181 
182 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
183 Note: pos is measured  in  bytes.  If   we  use  wchar  encoding we must
184 compensate for this.
185 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
186 
187 static long
Sseek_object(void * handle,long pos,int whence)188 Sseek_object(void *handle, long pos, int whence)
189 { OpenObject h = handle;
190   Int size;
191   int usize = (h->encoding == ENC_WCHAR ? sizeof(wchar_t) : 1);
192 
193   pos /= usize;
194 
195   if ( isFreedObj(h->object) )
196   { errno = EIO;
197     return -1;
198   }
199 
200   switch(whence)
201   { case SIO_SEEK_SET:
202       h->point = pos;
203       break;
204     case SIO_SEEK_CUR:
205       h->point += pos;			/* check for end!? */
206       break;
207     case SIO_SEEK_END:
208     { if ( hasGetMethodObject(h->object, NAME_sizeAsFile) &&
209 	   (size = get(h->object, NAME_sizeAsFile, EAV)) )
210       { h->point = valInt(size) - pos;
211 	break;
212       } else
213       { errno = EPIPE;			/* better idea? */
214 	return -1;
215       }
216     }
217     default:
218     { errno = EINVAL;
219       return -1;
220     }
221   }
222 
223   return h->point * usize;
224 }
225 
226 
227 static int
Sclose_object(void * handle)228 Sclose_object(void *handle)
229 { OpenObject h = handle;
230 
231   if ( isFreedObj(h->object) )
232   { errno = EIO;
233     return -1;
234   }
235 
236   delCodeReference(h->object);
237   freeableObj(h->object);
238 
239   unalloc(sizeof(*h), h);
240 
241   return 0;
242 }
243 
244 
245 static IOFUNCTIONS Sobjectfunctions =
246 { Sread_object,
247   Swrite_object,
248   Sseek_object,
249   Sclose_object
250 };
251 
252 
253 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
254 Note that files have their own  open/close.   In  the old days that used
255 stdio FILE*. Now that they both use IOSTREAM*, this should be merged.
256 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
257 
258 IOSTREAM *
Sopen_object(Any obj,const char * mode)259 Sopen_object(Any obj, const char *mode)
260 { if ( instanceOfObject(obj, ClassFile) )
261   { Name name = getOsNameFile(obj);
262     IOSTREAM *s;
263 
264     if ( (s=Sopen_file(nameToFN(name), mode)) )
265     { if ( !strchr(mode, 'b') )
266       { FileObj f = obj;
267 	Name oldstat = f->status;
268 	IOSTREAM *ofd = f->fd;
269 	int rc;
270 
271 					/* HACKS */
272 	f->status = (mode[0] == 'r' ? NAME_read : NAME_write);
273 	f->fd = s;
274 
275 	switch(mode[0])
276 	{ case 'r':
277 	  { if ( (rc = doBOMFile(f)) )
278 	      setStreamEncodingSourceSink(obj, s);
279 	    break;
280 	  }
281 	  case 'w':
282 	  { setStreamEncodingSourceSink(obj, s);
283 	    rc = doBOMFile(f);
284 	    break;
285 	  }
286 	  default:
287 	  { setStreamEncodingSourceSink(obj, s);
288 	    rc = 0;
289 	  }
290 	}
291 
292 	s->newline = (f->newline_mode == NAME_posix ? SIO_NL_POSIX :
293 		      f->newline_mode == NAME_dos   ? SIO_NL_DOS :
294 						      SIO_NL_DETECT);
295 
296 	f->fd = ofd;
297 	f->status = oldstat;
298 	if ( !rc )
299 	  return NULL;
300       }
301       return s;
302     }
303 
304     errorPce(obj, NAME_openFile,
305 	     mode[0] == 'r' ? NAME_read : NAME_write,
306 	     getOsErrorPce(PCE));
307 
308     return s;
309   } else if ( instanceOfObject(obj, ClassRC) &&
310 	      TheCallbackFunctions.rc_open )
311   { IOSTREAM *s;
312     RC rc = obj;
313     char *rc_class;
314 
315     if ( notDefault(rc->rc_class) )
316       rc_class = strName(rc->rc_class);
317     else
318       rc_class = NULL;
319 
320     if ( notNil(rc->context) && TheCallbackFunctions.setHostContext )
321     { Any savedcontext =
322 	(*TheCallbackFunctions.setHostContext)(rc->context);
323 
324       s = (*TheCallbackFunctions.rc_open)(strName(rc->name),
325 					  rc_class,
326 					  mode);
327       (*TheCallbackFunctions.setHostContext)(savedcontext);
328     } else
329       s = (*TheCallbackFunctions.rc_open)(strName(rc->name),
330 					  rc_class,
331 					  mode);
332 
333     if ( !s )
334       errorPce(obj, NAME_openFile,
335 	       mode[0] == 'r' ? NAME_read : NAME_write,
336 	       getOsErrorPce(PCE));
337 
338     return s;
339   } else
340   { int flags = SIO_TEXT|SIO_RECORDPOS;
341     OpenObject h;
342     IOSTREAM *stream;
343 
344     switch(mode[0])
345     { case 'r':
346 	flags |= SIO_INPUT;
347         break;
348       case 'w':
349 	flags |= SIO_OUTPUT;
350         break;
351       default:
352 	errno = EINVAL;
353         return NULL;
354     }
355 
356     for(mode++; *mode; mode++)
357     { switch(*mode)
358       { case 'b':			/* binary */
359 	  flags &= ~SIO_TEXT;
360 	  break;
361 	case 'r':			/* no record */
362 	  flags &= ~SIO_RECORDPOS;
363 	  break;
364 	default:
365 	  errno = EINVAL;
366 	  return NULL;
367       }
368     }
369 
370     h = alloc(sizeof(*h));
371     h->point = 0;
372     h->object = obj;
373     addCodeReference(obj);
374 
375     stream = Snew(h, flags, &Sobjectfunctions);
376 
377     if ( (flags&SIO_TEXT) )
378       stream->encoding = ENC_WCHAR;	/* see comment above */
379     else
380       stream->encoding = ENC_OCTET;
381     h->encoding = stream->encoding;
382 
383     return stream;
384   }
385 }
386