[BACK]Return to io.texi CVS log [TXT][DIR] Up to [local] / OpenXM / src / asir-doc / parts / builtin

Annotation of OpenXM/src/asir-doc/parts/builtin/io.texi, Revision 1.15

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

FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>