[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.17

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

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