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