Annotation of OpenXM/src/asir-doc/parts/builtin/io.texi, Revision 1.5
1.5 ! noro 1: @comment $OpenXM: OpenXM/src/asir-doc/parts/builtin/io.texi,v 1.4 2000/04/28 08:12:01 noro Exp $
1.2 noro 2: \BJP
1.1 noro 3: @node $BF~=PNO(B,,, $BAH$_9~$_H!?t(B
4: @section $BF~=PNO(B
1.2 noro 5: \E
6: \BEG
7: @node Inputs and Outputs,,, Built-in Function
8: @section Inputs and Outputs
9: \E
1.1 noro 10:
11: @menu
12: * end quit::
13: * load::
14: * which::
15: * output::
16: * bsave bload::
17: * bload27::
18: * print::
1.5 ! noro 19: * open_file close_file get_line get_byte purge_stdin::
1.1 noro 20: @end menu
21:
1.2 noro 22: \JP @node end quit,,, $BF~=PNO(B
23: \EG @node end quit,,, Inputs and Outputs
1.1 noro 24: @subsection @code{end}, @code{quit}
25: @findex end
26: @findex quit
27:
28: @table @t
29: @item end, quit
1.2 noro 30: \BJP
1.1 noro 31: :: $B8=:_FI$_9~$_Cf$N%U%!%$%k$rJD$8$k(B.
32: $B%H%C%W%l%Y%k$K$*$$$F$O%;%C%7%g%s$r=*N;$9$k$3$H$K$J$k(B.
1.2 noro 33: \E
34: \BEG
35: :: Close the currently reading file.
36: At the top level, terminate the @b{Asir} session.
37: \E
1.1 noro 38: @end table
39:
40: @itemize @bullet
1.2 noro 41: \BJP
1.1 noro 42: @item
43: @code{end}, @code{quit} $B$H$b$KL50z?t$NH!?t$G$"$k$,(B, @samp{()} $B$J$7$G(B
44: $B8F$S=P$9$3$H$,$G$-$k(B. $B$$$:$l$b8=:_FI$_9~$_Cf$N%U%!%$%k$rJD$8$k(B.
45: $B$3$l$O(B, $B%H%C%W%l%Y%k$K$*$$$F$O%;%C%7%g%s$r=*N;$5$;$k$3$H$K$J$k(B.
46: @item
47: $B%U%!%$%k$N>l9g(B, $B%U%!%$%k$N=*C<$^$GFI$a$P(B, $B<+F0E*$K%U%!%$%k$OJD$8$i$l$k(B
48: $B$,(B, $B%H%C%W%l%Y%k$N>l9g%W%m%s%W%H$,=P$J$$$^$^(B, $BF~NOBT$A$K$J$k$N$G(B,
49: $B%U%!%$%k$N=*C<$K$O(B @code{end$} $B$r=q$/$N$,K>$^$7$$(B.
1.2 noro 50: \E
51: \BEG
52: @item
53: These two functions take no arguments. These functions can be called
54: without a @samp{()}. Either function close the current input file.
55: This means the termination of the @b{Asir} session at the top level.
56: @item
57: An input file will be automatically closed if it is read to its end.
58: However, if no @code{end$} is written at the last of the input file,
59: the control will be returned to the top level and @b{Asir} will be
60: waiting for an input without any prompting.
61: Thus, in order to avoid confusion, putting a @code{end$} at the last
62: line of the input file is strongly recommended.
63: \E
1.1 noro 64: @end itemize
65:
66: @example
67: [6] quit;
68: %
69: @end example
70:
71: @table @t
1.2 noro 72: \JP @item $B;2>H(B
73: \EG @item References
1.1 noro 74: @fref{load}.
75: @end table
76:
1.2 noro 77: \JP @node load,,, $BF~=PNO(B
78: \EG @node load,,, Inputs and Outputs
1.1 noro 79: @subsection @code{load}
80: @findex load
81:
82: @table @t
83: @item load("@var{filename}")
1.2 noro 84: \JP :: @var{filename} $B$rFI$_9~$`(B.
1.3 noro 85: \EG :: Reads a program file @var{filename}.
1.1 noro 86: @end table
87:
88: @table @var
89: @item return
90: (1|0)
91: @item filename
1.2 noro 92: \JP $B%U%!%$%kL>(B ($B%Q%9L>(B)
93: \EG file (path) name
1.1 noro 94: @end table
95:
96: @itemize @bullet
1.2 noro 97: \BJP
1.1 noro 98: @item
99: $B<B:]$N%W%m%0%i%`$N=q$-J}$O(B, @xref{$B%f!<%68@8l(B Asir}.
100: $B%F%-%9%H%U%!%$%k$rFI$_9~$`>l9g(B, @code{cpp}
101: $B$rDL$9$N$G(B, C $B$N%W%m%0%i%`F1MM(B @code{#include}, @code{#define} $B$r;H$&$3$H$,$G$-$k(B.
102: @item
103: $B;XDj$7$?%U%!%$%k$,B8:_$7$?;~$K$O(B 1 $B$rJV$7(B, $BB8:_$7$J$+$C$?;~$O(B 0 $B$rJV$9(B.
104: @item
105: $B%U%!%$%kL>$,(B @samp{/} $B$G;O$^$k>l9g$O@dBP%Q%9(B, @samp{.} $B$G;O$^$k>l9g$O(B
106: $B%+%l%s%H%G%#%l%/%H%j$+$i$NAjBP%Q%9$H8+$J$5$l$k(B. $B$=$l0J30$N>l9g(B,
107: $B4D6-JQ?t(B @code{ASIRLOADPATH} $B$K@_Dj$5$l$F$$$k%G%#%l%/%H%j$r:8$+$i=g$K(B
108: $B%5!<%A$9$k(B. $B$=$l$i$K3:Ev$9$k%U%!%$%k$,B8:_$7$J$$>l9g(B, $BI8=`%i%$%V%i%j(B
109: $B%G%#%l%/%H%j(B ($B$"$k$$$O4D6-JQ?t(B @code{ASIR_LIBDIR} $B$K@_Dj$5$l$F$$$k(B
110: $B%G%#%l%/%H%j(B) $B$b%5!<%A$9$k(B.
1.2 noro 111: Windows $BHG$N>l9g(B, @code{ASIR_LIBDIR} $B$,@_Dj$5$l$F$$$J$$>l9g$K$O(B,
112: @code{get_rootdir()/lib} $B$r%5!<%A$9$k(B.
1.1 noro 113: @item
114: $BFI$_9~$`%U%!%$%k$N:G8e$K(B, @code{end$} $B$,$J$$$H(B @code{load()}
115: $B=*N;8e$K%W%m%s%W%H$,$G$J$$$,(B, $B<B:]$K$OF~NO$r<u$1IU$1$k(B. $B$7$+$7(B,
116: $B:.Mp$r>7$/$*$=$l$,$"$k$N$G%U%!%$%k$N:G8e$K(B @code{end$} $B$r=q$$$F$*$/$3$H(B
117: $B$,K>$^$7$$(B. (@code{end;} $B$G$b$h$$$,(B, @code{end} $B$,JV$9CM(B 0 $B$,I=<($5$l$k(B
118: $B$?$a(B, @code{end$} $B$r$*4+$a$9$k(B. )
119: @item
120: Windows $BHG$b%G%#%l%/%H%j$N%;%Q%l!<%?$H$7$F(B @samp{/} $B$rMQ$$$k(B.
1.2 noro 121: \E
122: \BEG
123: @item
124: @xref{User language Asir} for practical programming.
125: Since text files are read through @code{cpp},
126: the user can use, as in C programs, @code{#include} and @code{#define}
127: in @b{Asir} program source codes.
128: @item
129: It returns 1 if the designated file exists, 0 otherwise.
130: @item
131: If the @var{filename} begins with @samp{/}, it is understood as an
132: absolute path name; with @samp{.}, relative path name from current
133: directory; otherwise, the file is searched first from directories
134: assigned to an environmental variable @code{ASIRLOADPATH}, then
135: if the search ends up in failure, the standard library directory
136: (or directories assigned to @code{ASIR_LIBDIR}) shall be searched.
137: On Windows, @code{get_rootdir()/lib} is searched if
138: @code{ASIR_LIBDIR} is not set.
139: @item
140: We recommend to write an @code{end} command at the last line of
141: your program. If not, @b{Asir} will not give you a prompt after it
142: will have executed @code{load} command.
143: (Escape with an interrupt character (@pxref{Interruption}),
144: if you have lost yourself.)
145: Even in such a situation,
146: @b{Asir} itself is still ready to read keyboard inputs as usual.
147: It is, however, embarrassing and may cause other errors.
148: Therefore, to put an @code{end$} at the last line is desirable.
149: (Command @code{end;} will work as well,
150: but it also returns and displays verbose.)
151: @item
152: On Windows one has to use @samp{/} as the separator of directory names.
153: \E
1.1 noro 154: @end itemize
155:
156: @table @t
1.2 noro 157: \JP @item $B;2>H(B
158: \EG @item References
1.1 noro 159: @fref{end quit}, @fref{which}, @fref{get_rootdir}.
160: @end table
161:
1.2 noro 162: \JP @node which,,, $BF~=PNO(B
163: \EG @node which,,, Inputs and Outputs
1.1 noro 164: @subsection @code{which}
165: @findex which
166:
167: @table @t
168: @item which("@var{filename}")
1.2 noro 169: \JP :: $B0z?t(B @var{filename} $B$KBP$7(B, @code{load()} $B$,FI$_9~$`%Q%9L>$rJV$9(B.
170: \EG :: This returns the path name for the @var{filename} which @code{load()} will read.
1.1 noro 171: @end table
172:
173: @table @var
174: @item return
1.2 noro 175: \JP $B%Q%9L>(B
176: \EG path name
1.1 noro 177: @item filename
1.2 noro 178: \JP $B%U%!%$%kL>(B ($B%Q%9L>(B) $B$^$?$O(B 0
179: \EG filename (path name) or 0
1.1 noro 180: @end table
181:
182: @itemize @bullet
1.2 noro 183: \BJP
1.1 noro 184: @item
185: @code{load()} $B$,%U%!%$%k$r%5!<%A$9$k<j=g$K=>$C$F%5!<%A$7(B,
186: $B%U%!%$%k$,B8:_$9$k>l9g$K$O%Q%9L>$rJ8;zNs$H$7$F(B, $BB8:_$7$J$$>l9g(B
187: $B$K$O(B 0 $B$rJV$9(B.
188: @item
189: $B%5!<%A$N<j=g$K$D$$$F$O(B @code{load()} $B$r;2>H(B.
190: @item
191: Windows $BHG$b%G%#%l%/%H%j$N%;%Q%l!<%?$H$7$F(B @samp{/} $B$rMQ$$$k(B.
1.2 noro 192: \E
193: \BEG
194: @item
195: This function searches directory trees according to the same procedure
196: as @code{load()} will do. Then, returns a string, the path name to the
197: file if the named file exists; 0 unless otherwise.
198: @item
199: For details of searching procedure,
200: refer to the description about @code{load()}.
201: @item
202: On Windows one has to use @samp{/} as the separator of directory names.
203: \E
1.1 noro 204: @end itemize
205:
206: @example
207: [0] which("gr");
208: ./gb/gr
209: [1] which("/usr/local/lib/gr");
210: 0
211: [2] which("/usr/local/lib/asir/gr");
212: /usr/local/lib/asir/gr
213: @end example
214:
215: @table @t
1.2 noro 216: \JP @item $B;2>H(B
217: \EG @item References
1.1 noro 218: @fref{load}.
219: @end table
220:
1.2 noro 221: \JP @node output,,, $BF~=PNO(B
222: \EG @node output,,, Inputs and Outputs
1.1 noro 223: @subsection @code{output}
224: @findex output
225:
226: @table @t
227: @item output(["@var{filename}"])
1.2 noro 228: \JP :: $B0J9_$N=PNO@h$r(B @var{filename}$B$^$?$OI8=`=PNO$K@ZBX$($k(B.
229: \EG :: Writes the return values and prompt onto file @var{filename}.
1.1 noro 230: @end table
231:
232: @table @var
233: @item return
234: 1
235: @item filename
1.2 noro 236: \JP $B%U%!%$%kL>(B
237: \EG filename
1.1 noro 238: @end table
239:
240: @itemize @bullet
1.2 noro 241: \BJP
1.1 noro 242: @item
243: @b{Asir} $B$N=PNO$rI8=`=PNO$+$i(B, $B%U%!%$%k$X$N=PNO$K@ZBX$($k(B.
244: $B$J$*(B, $B%U%!%$%k=PNO$N4V$O(B, $BI8=`=PNO$K$O%-!<%\!<%I$+$i$NF~NO0J30(B,
245: $B=PNO$5$l$J$$(B.
246: @item
247: $BJL$N%U%!%$%k=PNO$K@ZBX$($k;~$K$O(B, $B:F$S(B @code{output("@var{filename}")}
248: $B$r<B9T$9$k(B.
249: $BKt(B, $B%U%!%$%k=PNO$r=*N;$7I8=`=PNO$KLa$j$?$$;~$K$O(B, $B0z?t$J$7$G(B
250: @code{output()} $B$r<B9T$9$k(B.
251: @item
252: $B;XDj$7$?%U%!%$%k(B @var{filename} $B$,B8:_$7$?;~$O(B, $B$=$N%U%!%$%k$NKvHx$K(B
253: $BDI=q$-$5$l(B, $BB8:_$7$J$+$C$?;~$K$O(B, $B?7$?$K%U%!%$%k$r:n@.$7(B, $B$=$3$K=q$-9~$^$l$k(B.
254: @item
255: $B%U%!%$%k%M!<%`$r(B "" $B%@%V%k%/%)!<%H$J$7$G;XDj$r$7$?$j(B,
256: $B%f!<%6$,(B, $B=q$-9~$a$J$$%U%!%$%k$r;XDj$7$?$j$9$k$H(B,
257: $B%(%i!<$K$h$j%H%C%W%l%Y%k$KLa$k(B.
258: @item
259: $BF~NO$7$?$b$N$b9~$a$F%U%!%$%k$K=PNO$7$?$$>l9g$K$O(B, @code{ctrl("echo",1)}
260: $B$r<B9T$7$?8e$G%U%!%$%k=PNO$K@ZBX$($l$PNI$$(B.
261: @item
262: $B7W;;;~4V$J$I(B, $BI8=`%(%i!<=PNO$K=q$-=P$5$l$k$b$N$O%U%!%$%k$K$O=q$-=P$5$l$J$$(B.
263: @item
264: $BH!?t7A<0(B, $BL$Dj78?t(B (@code{vtype()} $B;2>H(B) $B$r4^$^$J$$?t<0$N%U%!%$%k$X$NFI$_=q$-$O(B,
265: @code{bload()}, @code{bsave()} $B$r;H$&$N$,(B, $B;~4V(B, $B6u4V$H$b$K8zN($,$h$$(B.
266: @item
267: Windows $BHG$b%G%#%l%/%H%j$N%;%Q%l!<%?$H$7$F(B @samp{/} $B$rMQ$$$k(B.
1.2 noro 268: \E
269: \BEG
270: @item
271: Standard output stream of @b{Asir} is redirected to the specified file.
272: While @b{Asir} is writing its outputs onto a file, no outputs, except for
273: keyboard inputs and some of error messages, are written onto the standard
274: output. (You cannot see the result on the display.)
275: @item
276: To direct the @b{Asir} outputs to the standard output, issue the command
277: without argument, i.e., @code{output()}.
278: @item
279: If the specified file already exists, new outputs will be added to the
280: tail of the file. If not, a file is newly created and the outputs
281: will be written onto the file.
282: @item
283: When file name is specified without double quotes (@code{""}), or
284: when protected file is specified, an error occurs and the system returns
285: to the top level.
286: @item
287: If you want to write inputs from the key board onto the file as well
288: as @b{Asir} outputs, put command @code{ctrl("echo",1)}, and then
289: redirect the standard output to your desired file.
290: @item
291: Contents which are written onto the standard error output, CPU time etc.,
292: are not written onto the file.
293: @item
294: Reading and writing algebraic expressions which contain neither
295: functional forms nor unknown coefficients (@code{vtype()} References)
296: are performed more efficiently, with respect to both time and space,
297: by @code{bload()} and @code{bsave()}.
298: @item
299: On Windows one has to use @samp{/} as the separator of directory names.
300: \E
1.1 noro 301: @end itemize
302:
303: @example
304: [83] output("afo");
305: fctr(x^2-y^2);
306: print("afo");
307: output();
308: 1
309: [87] quit;
310: % cat afo
311: 1
312: [84] [[1,1],[x+y,1],[x-y,1]]
313: [85] afo
314: 0
315: [86]
316: @end example
317:
318: @table @t
1.2 noro 319: \JP @item $B;2>H(B
320: \EG @item References
1.1 noro 321: @fref{ctrl}, @fref{bsave bload}.
322: @end table
323:
1.2 noro 324: \JP @node bsave bload,,, $BF~=PNO(B
325: \EG @node bsave bload,,, Inputs and Outputs
1.1 noro 326: @subsection @code{bsave}, @code{bload}
327: @findex bsave
328: @findex bload
329:
330: @table @t
331: @item bsave(@var{obj},"@var{filename}")
1.2 noro 332: \JP :: @var{filename} $B$K(B @var{obj} $B$r%P%$%J%j7A<0$G=q$-9~$`(B.
333: \EG :: This function writes @var{obj} onto @var{filename} in binary form.
1.4 noro 334: @item bload("@var{filename}")
1.2 noro 335: \JP :: @var{filename} $B$+$i?t<0$r%P%$%J%j7A<0$GFI$_9~$`(B.
336: \EG :: This function reads an expression from @var{filename} in binary form.
1.1 noro 337: @end table
338:
339: @table @var
340: @item return
1.2 noro 341: \JP @code{bsave()} : 1, @code{bload()} : $BFI$_9~$s$@?t<0(B
342: \EG @code{bsave()} : 1, @code{bload()} : the expression read
1.1 noro 343: @item obj
1.2 noro 344: \JP $BH!?t7A<0(B, $BL$Dj78?t$r4^$^$J$$G$0U$N?t<0(B
345: \BEG
346: arbitrary expression which does not contain neither function forms
347: nor unknown coefficients.
348: \E
1.1 noro 349: @item filename
1.2 noro 350: \JP $B%U%!%$%kL>(B
351: \EG filename
1.1 noro 352: @end table
353:
354: @itemize @bullet
1.2 noro 355: \BJP
1.1 noro 356: @item
357: @code{bsave()} $B$OFbIt7A<0$r$[$\$=$N$^$^%P%$%J%j7A<0$G%U%!%$%k$K=q$-9~$`(B.
358: @code{bload()} $B$O(B, @code{bsave()} $B$G=q$-9~$s$@?t<0$rFI$_9~$s$GFbIt7A<0(B
359: $B$KJQ49$9$k(B. $B8=:_$N%$%s%W%j%a%s%F!<%7%g%s$N@)8B$K$h$j(B, $BH!?t7A<0(B, $BL$Dj78?t(B
360: (@code{vtype()} $B;2>H(B) $B$r4^$^$J$$%j%9%H(B, $BG[Ns$J$I$r4^$`G$0U$N?t<0$r%U%!(B
361: $B%$%k$KJ]B8$9$k$3$H$,$G$-$k(B.
362: @item
363: @code{output()} $B$J$I$GJ]B8$7$?>l9g(B, $BFI$_9~$_;~$K%Q!<%6$,5/F0$5$l$k$,(B,
364: @code{bsave()} $B$GJ]B8$7$?$b$N$r(B @code{bload()} $B$GFI$`>l9g(B, $BD>@\(B
365: $BFbIt7A<0$,9=@.$G$-$k$?$a(B, $B;~4VE*(B, $B6u4VE*$K8zN($,$h$$(B.
366: @item
367: $BB?9`<0$N>l9g(B, $B=q$-9~$_;~$HFI$_9~$_;~$GJQ?t=g=x$,0[$J$k>l9g$,$"$k$,(B,
368: $B$=$N>l9g$K$O(B, $B<+F0E*$K8=:_$NJQ?t=g=x$K$*$1$kFbIt7A<0$KJQ49$5$l$k(B.
369: @item
370: Windows $BHG$b%G%#%l%/%H%j$N%;%Q%l!<%?$H$7$F(B @samp{/} $B$rMQ$$$k(B.
1.2 noro 371: \E
372: \BEG
373: @item
374: Function @code{bsave()} writes an object onto a file in its internal
375: form (not exact internal form but very similar).
376: Function @code{bload()} read the expression from files
377: which is written by @code{bsave()}.
378: Current implementation support arbitrary expressions, including
379: lists, arrays (i.e., vectors and matrices), except for function forms
380: and unknown coefficients (@code{vtype()} References.)
381: @item
382: The parser is activated to retrieve expressions written by
383: @code{output()} , whereas internal forms are directly reconstructed
384: by @code{bload()} from the @code{bsave()}'ed object in the file.
385: The latter is much more efficient with respect to both time and space.
386: @item
387: It may happen that the variable ordering at reading is changed from
388: that at writing. In such a case, the variable ordering in the internal
389: expression is automatically rearranged according to the current
390: variable ordering.
391: @item
392: On Windows one has to use @samp{/} as the separator of directory names.
393: \E
1.1 noro 394: @end itemize
395:
396: @example
397: [0] A=(x+y+z+u+v+w)^20$
398: [1] bsave(A,"afo");
399: 1
400: [2] B = bload("afo")$
401: [3] A == B;
402: 1
403: [4] X=(x+y)^2;
404: x^2+2*y*x+y^2
405: [5] bsave(X,"afo")$
406: [6] quit;
407: % asir
408: [0] ord([y,x])$
409: [1] bload("afo");
410: y^2+2*x*y+x^2
411: @end example
412:
413: @table @t
1.2 noro 414: \JP @item $B;2>H(B
415: \EG @item References
1.1 noro 416: @fref{output}.
417: @end table
418:
1.2 noro 419: \JP @node bload27,,, $BF~=PNO(B
420: \EG @node bload27,,, Inputs and Outputs
1.1 noro 421: @subsection @code{bload27}
422: @findex bload27
423:
424: @table @t
1.4 noro 425: @item bload27("@var{filename}")
1.2 noro 426: \JP :: $B5lHG$G:n$i$l$?(B bsave file $B$NFI$_9~$_(B
427: \EG :: Reads bsaved file created by older version of @b{Asir}.
1.1 noro 428: @end table
429:
430: @table @var
431: @item return
1.2 noro 432: \JP $BFI$_9~$s$@?t<0(B
433: \EG expression read
1.1 noro 434: @item filename
1.2 noro 435: \JP $B%U%!%$%kL>(B
436: \EG filename
1.1 noro 437: @end table
438:
439: @itemize @bullet
1.2 noro 440: \BJP
1.1 noro 441: @item
442: $B5lHG$G$O(B, $BB?G\D9@0?t$,(B, 1 $B%o!<%I(B 27 bit $B$GI=8=$5$l$F$$$?$,(B, $B?7HG$G$O(B 1 $B%o!<%I(B 32 bit
443: $B$KJQ99$5$l$?(B. $B$3$N$?$a(B, $B5lHG$G(B @code{bsave} $B$5$l$?%P%$%J%j%U%!%$%k$O$=$N$^$^$G$O(B
444: $BFI$_9~$a$J$$(B. $B$3$N$h$&$J%U%!%$%k$rFI$_9~$`$?$a$K(B @code{bload27} $B$rMQ$$$k(B.
445: @item
446: Windows $BHG$b%G%#%l%/%H%j$N%;%Q%l!<%?$H$7$F(B @samp{/} $B$rMQ$$$k(B.
1.2 noro 447: \E
448: \BEG
449: @item
450: In older versions an arbitrary precision integer is represented as
451: an array of 27bit integers. In the current version it is represented
452: as an array of 32bit integers. By this incompatibility the bsaved
453: file created by older versions cannot be read in the current version
454: by @code{bload}.
455: @code{bload27} is used to read such files.
456: @item
457: On Windows one has to use @samp{/} as the separator of directory names.
458: \E
1.1 noro 459: @end itemize
460:
461: @table @t
1.2 noro 462: \JP @item $B;2>H(B
463: \EG @item References
1.1 noro 464: @fref{bsave bload}.
465: @end table
466:
1.2 noro 467: \JP @node print,,, $BF~=PNO(B
468: \EG @node print,,, Inputs and Outputs
1.1 noro 469: @subsection @code{print}
470: @findex print
471:
472: @table @t
473: @item print(@var{obj} [,@var{nl}])
1.2 noro 474: \JP :: @var{obj} $B$rI=<($9$k(B.
475: \EG :: Displays (or outputs) @var{obj}.
1.1 noro 476: @end table
477:
478: @table @var
479: @item return
480: 0
481: @item obj
1.2 noro 482: \JP $BG$0U(B
483: \EG arbitrary
1.1 noro 484: @item nl
1.2 noro 485: \JP $B%U%i%0(B ($BG$0U(B)
486: \EG flag (arbitrary)
1.1 noro 487: @end table
488:
489: @itemize @bullet
1.2 noro 490: \BJP
1.1 noro 491: @item
492: @var{obj} $B$rI>2A$7$FI=<($9$k(B.
493: @item
494: $BBh(B 2 $B0z?t$,$J$$$+(B, $B$^$?$O(B 0, 2 $B0J30$N>l9g(B, $B2~9T$9$k(B.
495: $BBh(B 2 $B0z?t$,(B 1 $B$N>l9g(B, $B2~9T$;$:(B, $B=PNO$O%P%C%U%!$K=q$-9~$^$l(B,
496: $B%P%C%U%!$O%U%i%C%7%e$5$l$J$$(B.
497: $BBh(B 2 $B0z?t$,(B 2 $B$N>l9g(B, $B2~9T$7$J$$$,%P%C%U%!$O%U%i%C%7%e$5$l$k(B.
498: @item
499: $B$3$NH!?t$NLa$jCM$O(B 0 $B$G$"$k$+$i(B, @code{print();}
500: $B$G<B9T$9$k$H(B, $B=PNO$N8e$K(B 0 $B$,JV$5$l$k(B.
501: @code{print()$} $B$H$9$l$P(B, $B:G8e$N(B 0 $B$O=PNO$5$l$J$$(B.
502: @item
503: $BJ#?t$N(B @var{obj} $B$rF1;~$K=PNO$7$?$$;~$O(B @var{obj} $B$r%j%9%H$K$9$k$H$h$$(B.
1.2 noro 504: \E
505: \BEG
506: @item
507: Displays (or outputs) @var{obj}.
508: @item
509: It normally adds linefeed code to cause the cursor moving to the next
510: line. If 0 or 2 is given as the second argument, it does not add a linefeed.
511: If the second argument is 0, the output is simply written in the buffer.
512: If the second argument is 2, the output is flushed.
513: @item
514: The return value of this function is 0.
515: If command @code{print(@var{rat});} is performed at the top level,
516: first the value of @var{rat} will be printed,
517: followed by a linefeed, followed by a 0 which is the value of the
518: function and followed by a linefeed and the next prompt.
519: (If the command is terminated by a `$', e.g., @code{print(@var{rat})$},
520: The last 0 will not be printed. )
521: @item
522: Formatted outputs are not currently supported.
523: If one wishes to output multiple objects by a single @code{print()} command,
524: use list like @code{[@var{obj1,...}]}, which is not so beautiful, but
525: convenient to minimize programming efforts.
526: \E
1.1 noro 527: @end itemize
528:
529: @example
530: [8] def cat(L) @{ while ( L != [] ) @{ print(car(L),0); L = cdr(L);@} print(""); @}
531: [9] cat([xyz,123,"gahaha"])$
532: xyz123gahaha
533: @end example
534:
1.5 ! noro 535: \JP @node open_file close_file get_line get_byte purge_stdin,,, $BF~=PNO(B
! 536: \EG @node open_file close_file get_line get_byte purge_stdin,,, Inputs and Outputs
! 537: @subsection @code{open_file}, @code{close_file}, @code{get_line}, @code{get_byte}, @code{purge_stdin}
1.3 noro 538: @findex open_file
539: @findex close_file
540: @findex get_line
1.5 ! noro 541: @findex get_byte
! 542: @findex purge_stdin
1.3 noro 543:
544: @table @t
545: @item open_file("@var{filename}")
546: \JP :: @var{filename} $B$rFI$_=P$7MQ$K%*!<%W%s$9$k(B.
547: \EG :: Opens @var{filename} for reading.
548: @item close_file(@var{num})
549: \JP :: $B<1JL;R(B @var{num} $B$N%U%!%$%k$r%/%m!<%:$9$k(B.
550: \EG :: Closes the file indicated by a descriptor @var{num}.
1.5 ! noro 551: @item get_line([@var{num}])
1.3 noro 552: \JP :: $B<1JL;R(B @var{num} $B$N%U%!%$%k$+$i(B 1 $B9TFI$`(B.
553: \EG :: Reads a line from the file indicated by a descriptor @var{num}.
1.5 ! noro 554: @item get_byte(@var{num})
! 555: \JP :: $B<1JL;R(B @var{num} $B$N%U%!%$%k$+$i(B 1 $B%P%$%HFI$`(B.
! 556: \EG :: Reads a byte from the file indicated by a descriptor @var{num}.
! 557: @item purge_stdin()
! 558: \JP :: $BI8=`F~NO$N%P%C%U%!$r%/%j%"$9$k(B.
! 559: \EG :: Clears the buffer for the standard input.
1.3 noro 560: @end table
561:
562: @table @var
563: @item return
1.5 ! noro 564: \JP @code{open_file()} : $B@0?t(B ($B<1JL;R(B); @code{close_file()} : 1; @code{get_line()} : $BJ8;zNs(B, @code{get_byte()} : $B@0?t(B
! 565: \EG @code{open_file()} : integer (fild id); @code{close_file()} : 1; @code{get_line()} : string, @code{get_byte()} : integer
1.3 noro 566: @item filename
567: \JP $B%U%!%$%kL>(B ($B%Q%9L>(B)
568: \EG file (path) name
569: @item num
570: \JP $BHsIi@0?t(B ($B%U%!%$%k<1JL;R(B)
571: \EG non-negative integer (file descriptor)
572: @end table
573:
574: @itemize @bullet
575: \BJP
576: @item @code{open_file()} $B$OFI$_=P$7MQ$K%U%!%$%k$r%*!<%W%s$9$k(B. $B@.8y$7$?(B
577: $B>l9g(B, $B%U%!%$%k<1JL;R$H$7$FHsIi@0?t$rJV$9(B. $B<:GT$N>l9g%(%i!<$H$J$k(B.
578: $BITMW$K$J$C$?%U%!%$%k$O(B @code{close_file()} $B$G%/%m!<%:$9$k(B.
579: @item @code{get_line()} $B$O8=:_%*!<%W%s$7$F$$$k%U%!%$%k$+$i(B 1 $B9TFI$_(B,
1.5 ! noro 580: $BJ8;zNs$H$7$FJV$9(B. $B0z?t$,$J$$>l9g(B, $BI8=`F~NO$+$i(B 1 $B9TFI$`(B.
! 581: @item @code{get_byte()} $B$O8=:_%*!<%W%s$7$F$$$k%U%!%$%k$+$i(B 1 $B%P%$%HFI$_(B
! 582: $B@0?t$H$7$FJV$9(B.
1.3 noro 583: @item $B%U%!%$%k$N=*$j$^$GFI$s$@8e$K(B @code{get_line()} $B$,8F$P$l$?>l9g(B,
584: $B@0?t$N(B 0 $B$rJV$9(B.
585: @item $BFI$_=P$7$?J8;zNs$O(B, $BI,MW$,$"$l$P(B @code{sub_str()} $B$J$I$NJ8;zNs=hM}(B
586: $B4X?t$G2C9)$7$?$N$A(B @code{eval_str()} $B$K$h$jFbIt7A<0$KJQ49$G$-$k(B.
1.5 ! noro 587: @item @code{purge_stdin()} $B$O(B, $BI8=`F~NO%P%C%U%!$r6u$K$9$k(B.
! 588: $B4X?tFb$G(B @code{get_line()} $B$K$h$jI8=`F~NO$+$iJ8;zNs$r<u$1<h$k>l9g(B,
! 589: $B4{$K%P%C%U%!Fb$KB8:_$9$kJ8;zNs$K$h$k8mF0:n$rKI$0$?$a$K$"$i$+$8$a(B
! 590: $B8F$S=P$9(B.
1.3 noro 591: \E
592: \BEG
593: @item @code{open_file()} opens a file for reading.
594: If successful, it returns a non-negative integer as the file descriptor.
595: Otherwise the system error function is called.
596: Unnecessary files should be closed by @code{close_file()}.
597: @item @code{get_line()} reads a line from an opened file and returns the
1.5 ! noro 598: line as a string. If no argument is supplied, it reads a line from the
! 599: standard input.
! 600: @item @code{get_byte()} reads a byte from an opened file and returns the
! 601: it as an integer.
1.3 noro 602: @item A @code{get_line()} call after reading the end of file returns
603: an integer 0.
604: @item Strings can be converted into internal forms with string manipulation
605: functions such as @code{sub_str()}, @code{eval_str()}.
1.5 ! noro 606: @item @code{purge_stdin()} clears the buffer for the standard input.
! 607: When a function receives a character string from @code{get_line()},
! 608: this functions should be called in advance in order to avoid
! 609: an incorrect behavior which is caused by the characters already
! 610: exists in the buffer.
1.3 noro 611: \E
612: @end itemize
613:
614: @example
615: [185] Id = open_file("test");
616: 0
617: [186] get_line(Id);
618: 12345
619:
620: [187] get_line(Id);
621: 67890
622:
623: [188] get_line(Id);
624: 0
625: [189] type(@@@@);
626: 0
1.5 ! noro 627: [190] close_file(Id);
! 628: 1
! 629: [191] open_file("test");
! 630: 1
! 631: [192] get_line(1);
! 632: 12345
! 633:
! 634: [193] get_byte(1);
! 635: 54 /* the ASCII code of '6' */
! 636: [194] get_line(1);
! 637: 7890 /* the rest of the last line */
! 638: [195] def test() @{ return get_line(); @}
! 639: [196] def test1() @{ purge_stdin(); return get_line(); @}
! 640: [197] test();
! 641: /* a remaining newline character has been read */
! 642: /* returns immediately */
! 643: [198] test1();
! 644: 123; /* input from a keyboard */
! 645: 123; /* returned value */
! 646:
! 647: [199]
! 648:
1.3 noro 649: @end example
650:
651: @table @t
652: \JP @item $B;2>H(B
653: \EG @item References
654: @fref{eval_str}, @fref{str_len str_chr sub_str}.
655: @end table
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>