r7rs-small-texinfo

Unnamed repository; edit this file 'description' to name the repository.
git clone https://kaka.farm/~git/r7rs-small-texinfo
Log | Files | Refs | README | LICENSE

program-structure.texinfo (23871B)


      1 @node Program structure
      2 @chapter Program structure
      3 
      4 @menu
      5 * Programs::
      6 * Import declarations::
      7 * Variable definitions::
      8 * Syntax definitions::
      9 * Record type definitions::
     10 * Libraries::
     11 * The REPL::
     12 @end menu
     13 
     14 @node Programs
     15 @section Programs
     16 
     17 A Scheme program consists of one or more import declarations followed
     18 by a sequence of expressions and definitions. Import declarations
     19 specify the libraries on which a program or library depends; a subset
     20 of the identifiers exported by the libraries are made available to the
     21 program. Expressions are described in @ref{Expressions}. Definitions
     22 are either variable definitions, syntax definitions, or record-type
     23 definitions, all of which are explained in this chapter. They are
     24 valid in some, but not all, contexts where expressions are allowed,
     25 specifically at the outermost level of a @svar{program} and at the
     26 beginning of a @svar{body}.
     27 
     28 At the outermost level of a program, @code{(begin }@svar{expression
     29 or definition@sub{1}} @dots{}@code{)} is equivalent to the sequence of
     30 expressions and definitions in the begin. Similarly, in a @svar{body},
     31 (begin @svar{definition@sub{1}} @dots{}) is equivalent to the sequence
     32 @svar{definition@sub{1}} @dots{}. Macros can expand into such begin
     33 forms. For the formal definition, see @ref{Sequencing}.
     34 
     35 Import declarations and definitions cause bindings to be created in the
     36 global environment or modify the value of existing global bindings. The
     37 initial environment of a program is empty, so at least one import
     38 declaration is needed to introduce initial bindings.
     39 
     40 Expressions occurring at the outermost level of a program do not create
     41 any bindings. They are executed in order when the program is invoked
     42 or loaded, and typically perform some kind of initialization.
     43 
     44 Programs and libraries are typically stored in files, although in
     45 some implementations they can be entered interactively into a running
     46 Scheme system. Other paradigms are possible. Implementations which store
     47 libraries in files should document the mapping from the name of a library
     48 to its location in the file system.
     49 
     50 @node Import declarations
     51 @section Import declarations
     52 
     53 An import declaration takes the following form:
     54 
     55 @lisp
     56 (import @r{@svar{import-set} @dots{}})
     57 @end lisp
     58 
     59 An import declaration provides a way to import identifiers exported by a
     60 library. Each @svar{import set} names a set of bindings from a library and
     61 possibly specifies local names for the imported bindings. It takes one of
     62 the following forms:
     63 
     64 @itemize
     65 
     66 @item
     67 @svar{library name}
     68 
     69 @item
     70 @code{(only }@svar{import set} @svar{identifier} @dots{}@code{)}
     71 
     72 @item
     73 @code{(except }@svar{import set} @svar{identifier} @dots{})
     74 
     75 @item
     76 @code{(prefix }@svar{import set} @svar{identifier})
     77 
     78 @item
     79 @code{(rename }@svar{import set}
     80 @code{(}@svar{identifier@sub{1}} @svar{identifier@sub{2}}@code{)}
     81 @dots{}@code{)}
     82 
     83 @end itemize
     84 
     85 In the first form, all of the identifiers in the named library's export
     86 clauses are imported with the same names (or the exported names if
     87 exported with rename). The additional @svar{import set} forms modify this
     88 set as follows:
     89 
     90 @itemize
     91 
     92 @item
     93 @code{only} produces a subset of the given @svar{import set} including
     94 only the listed identifiers (after any renaming). It is an error if any of
     95 the listed identifiers are not found in the original set.
     96 
     97 @item
     98 @code{except} produces a subset of the given @svar{import set}, excluding
     99 the listed identifiers (after any renaming). It is an error if any of the
    100 listed identifiers are not found in the original set.
    101 
    102 @item
    103 @code{rename} modifies the given @svar{import set}, replacing each
    104 instance of @svar{identifier@sub{1}} with @svar{identifier@sub{2}}. It is
    105 an error if any of the listed @svar{identifier@sub{1}}s are not found in
    106 the original set.
    107 
    108 @item
    109 @code{prefix} automatically renames all identifiers in the given
    110 @svar{import set}, prefixing each with the specified @svar{identifier}.
    111 
    112 @end itemize
    113 
    114 In a program or library declaration, it is an error to import the same
    115 identifier more than once with different bindings, or to redefine or
    116 mutate an imported binding with a definition or with @code{set!}, or to
    117 refer to an identifier before it is imported. However, a REPL should
    118 permit these actions.
    119 
    120 @node Variable definitions
    121 @section Variable definitions
    122 
    123 @findex define
    124 
    125 A variable definition binds one or more identifiers and specifies an
    126 initial value for each of them. The simplest kind of variable definition
    127 takes one of the following forms:
    128 
    129 @itemize
    130 
    131 @item
    132 @code{(define }@svar{variable} @svar{expression}@code{)}
    133 
    134 @item
    135 @code{(define }(@svar{variable} @svar{formals}@code{)} @svar{body}@code{)}
    136 
    137 @svar{Formals} are either a sequence of zero or more variables, or a
    138 sequence of one or more variables followed by a space-delimited period and
    139 another variable (as in a lambda expression). This form is equivalent to
    140 
    141 @lisp
    142 (define @r{@svar{variable}}
    143    (lambda (@r{@svar{formals}}) @r{@svar{body}}))@r{.}
    144 @end lisp
    145 
    146 @item
    147 @code{(define (}@svar{variable} @code{.} @svar{formal}@code{)} @svar{body}@code{)}
    148 
    149 @svar{Formal} is a single variable. This form is equivalent to
    150 
    151 @lisp
    152 (define @r{@svar{variable}}
    153    (lambda @r{@svar{formal}} @r{@svar{body}}))@r{.}
    154 @end lisp
    155 
    156 @end itemize
    157 
    158 @menu
    159 * Top level definitions::
    160 * Internal definitions::
    161 * Multiple value definitions::
    162 @end menu
    163 
    164 @node Top level definitions
    165 @subsection Top level definitions
    166 
    167 At the outermost level of a program, a definition
    168 
    169 @lisp
    170 (define @r{@svar{variable} @svar{expression}})
    171 @end lisp
    172 
    173 has essentially the same effect as the assignment
    174 expression
    175 
    176 @lisp
    177 (set! @r{@svar{variable} @svar{expression}})
    178 @end lisp
    179 
    180 if @svar{variable} is bound to a non-syntax value. However, if
    181 @svar{variable} is not bound, or is a syntactic keyword, then the
    182 definition will bind @svar{variable} to a new location before performing
    183 the assignment, whereas it would be an error to perform a @code{set!} on
    184 an unbound variable.
    185 
    186 @lisp
    187 (define add3
    188   (lambda (x) (+ x 3)))
    189 (add3 3)                @result{} 6
    190 (define first car)
    191 (first '(1 2))          @result{} 1
    192 @end lisp
    193 
    194 @node Internal definitions
    195 @subsection Internal definitions
    196 
    197 Definitions can occur at the beginning of a @svar{body} (that is,
    198 the body of a @code{lambda}, @code{let}, @code{let*}, @code{letrec},
    199 @code{letrec*}, @code{let-values}, @code{let*-values}, @code{let-syntax},
    200 @code{letrec-syntax}, @code{parameterize}, @code{guard}, or
    201 @code{case-lambda}). Note that such a body might not be apparent
    202 until after expansion of other syntax. Such definitions are known as
    203 @define{internal definitions} as opposed to the global definitions described
    204 above. The variables defined by internal definitions are local to the
    205 @svar{body}. That is, @svar{variable} is bound rather than assigned,
    206 and the region of the binding is the entire @svar{body}. For example,
    207 
    208 @lisp
    209 (let ((x 5))
    210   (define foo (lambda (y) (bar x y)))
    211   (define bar (lambda (a b) (+ (* a b) a)))
    212   (foo (+ x 3))) @result{} 45
    213 @end lisp
    214 
    215 An expanded @svar{body} containing internal definitions can always be
    216 converted into a completely equivalent @code{letrec*} expression. For
    217 example, the @code{let} expression in the above example is equivalent to
    218 
    219 @lisp
    220 (let ((x 5))
    221   (letrec* ((foo (lambda (y) (bar x y)))
    222             (bar (lambda (a b) (+ (* a b) a))))
    223     (foo (+ x 3))))
    224 @end lisp
    225 
    226 Just as for the equivalent @code{letrec*} expression, it is an error if
    227 it is not possible to evaluate each @svar{expression} of every internal
    228 definition in a @svar{body} without assigning or referring to the value
    229 of the corresponding @svar{variable} or the @svar{variable} of any of
    230 the definitions that follow it in @svar{body}.
    231 
    232 It is an error to define the same identifier more than once in the
    233 same @svar{body}.
    234 
    235 Wherever an internal definition can occur,
    236 @code{(begin }@svar{definition@sub{1}} @dots{}@code{)} is equivalent
    237 to the sequence of definitions that form the body of the @code{begin}.
    238 
    239 @node Multiple value definitions
    240 @subsection Multiple-value definitions
    241 
    242 Another kind of definition is provided by @code{define-values}, which
    243 creates multiple definitions from a single expression returning multiple
    244 values. It is allowed wherever define is allowed.
    245 
    246 @deffn syntax define-values @svar{formals} @svar{expression}
    247 
    248 It is an error if a variable appears more than once in the set of
    249 @svar{formals}.
    250 
    251 Semantics: @svar{Expression} is evaluated, and the @svar{formals} are
    252 bound to the return values in the same way that the @svar{formals} in a
    253 @code{lambda} expression are matched to the arguments in a procedure call.
    254 
    255 @lisp
    256 (define-values (x y) (exact-integer-sqrt 17))
    257 (list x y) @result{} (4 1)
    258 
    259 (let ()
    260   (define-values (x y) (values 1 2))
    261   (+ x y)) @result{} 3
    262 @end lisp
    263 
    264 @end deffn
    265 
    266 @node Syntax definitions
    267 @section Syntax definitions
    268 
    269 Syntax definitions have this form:
    270 
    271 @deffn syntax define-syntax @svar{keyword} @svar{transformer spec}
    272 
    273 @svar{Keyword} is an identifier, and the @svar{transformer spec} is
    274 an instance of @code{syntax-rules}. Like variable definitions, syntax
    275 definitions can appear at the outermost level or nested within a body.
    276 
    277 If the @code{define-syntax} occurs at the outermost level, then the global
    278 syntactic environment is extended by binding the @svar{keyword} to the
    279 specified transformer, but previous expansions of any global binding
    280 for @svar{keyword} remain unchanged. Otherwise, it is an @define{internal
    281 syntax definition}, and is local to the @svar{body} in which it is
    282 defined. Any use of a syntax keyword before its corresponding definition
    283 is an error. In particular, a use that precedes an inner definition will
    284 not apply an outer definition.
    285 
    286 @lisp
    287 (let ((x 1) (y 2))
    288   (define-syntax swap!
    289     (syntax-rules ()
    290       ((swap! a b)
    291        (let ((tmp a))
    292          (set! a b)
    293          (set! b tmp)))))
    294   (swap! x y)
    295   (list x y)) @result{} (2 1)
    296 @end lisp
    297 
    298 Macros can expand into definitions in any context that permits
    299 them. However, it is an error for a definition to define an identifier
    300 whose binding has to be known in order to determine the meaning of the
    301 definition itself, or of any preceding definition that belongs to the
    302 same group of internal definitions. Similarly, it is an error for an
    303 internal definition to define an identifier whose binding has to be known
    304 in order to determine the boundary between the internal definitions and
    305 the expressions of the body it belongs to. For example, the following
    306 are errors:
    307 
    308 @lisp
    309 (define define 3)
    310 
    311 (begin (define begin list))
    312 
    313 (let-syntax
    314     ((foo (syntax-rules ()
    315             ((foo (proc args ...) body ...)
    316              (define proc
    317                (lambda (args ...)
    318                  body ...))))))
    319   (let ((x 3))
    320     (foo (plus x y) (+ x y))
    321     (define foo x)
    322     (plus foo x)))
    323 @end lisp
    324 
    325 @end deffn
    326 
    327 @node Record type definitions
    328 @section Record-type definitions
    329 
    330 @define{Record-type definitions} are used to introduce new data types, called
    331 @define{record types}. Like other definitions, they can appear either at the
    332 outermost level or in a body. The values of a record type are called
    333 @define{records} and are aggregations of zero or more @define{fields}, each of
    334 which holds a single location. A predicate, a constructor, and field
    335 accessors and mutators are defined for each record type.
    336 
    337 @c FIXME: Should we "stub" this and put the actual syntax below?
    338 @deffn syntax define-record-type @svar{name} @svar{constructor} @svar{pred} @svar{field}@dots{}
    339 
    340 Syntax: @svar{name} and @svar{pred} are identifiers. The @svar{constructor} is of the form
    341 
    342 @display
    343 @code{(}@svar{constructor name} @svar{field name} @dots{}@code{)}
    344 @end display
    345 
    346 and each @svar{field} is either of the form
    347 
    348 @display
    349 @code{(}@svar{field name} @svar{accessor name}@code{)}
    350 @end display
    351 
    352 or of the form
    353 
    354 @display
    355 @code{(}@svar{field name} @svar{accessor name} @svar{modifier name}@code{)}
    356 @end display
    357 
    358 It is an error for the same identifier to occur more than once as a
    359 field name. It is also an error for the same identifier to occur more
    360 than once as an accessor or mutator name.
    361 
    362 The @code{define-record-type} construct is generative: each use creates
    363 a new record type that is distinct from all existing types, including
    364 Scheme's predefined types and other record types---even record types of
    365 the same name or structure.
    366 
    367 An instance of @code{define-record-type} is equivalent to the following
    368 definitions:
    369 
    370 @itemize
    371 
    372 @item
    373 @svar{name} is bound to a representation of the record type itself. This
    374 may be a run-time object or a purely syntactic representation. The
    375 representation is not utilized in this report, but it serves as a means to
    376 identify the record type for use by further language extensions.
    377 
    378 @item
    379 @svar{constructor name} is bound to a procedure that takes as many
    380 arguments as there are @svar{field name}s in the @code{(}@svar{constructor
    381 name} @dots{}@code{)} subexpression and returns a new record of type
    382 @svar{name}. Fields whose names are listed with @svar{constructor name}
    383 have the corresponding argument as their initial value. The initial values
    384 of all other fields are unspecified. It is an error for a field name to
    385 appear in @svar{constructor} but not as a <field name>.
    386 
    387 @item
    388 @svar{pred} is bound to a predicate that returns @code{#t} when given a
    389 value returned by the procedure bound to @svar{constructor name} and
    390 @code{#f} for everything else.
    391 
    392 @item
    393 Each @svar{accessor name} is bound to a procedure that takes a record of
    394 type @svar{name} and returns the current value of the corresponding field.
    395 It is an error to pass an accessor a value which is not a record of the
    396 appropriate type.
    397 
    398 @item
    399 Each @svar{modifier name} is bound to a procedure that takes a record of
    400 type @svar{name} and a value which becomes the new value of the
    401 corresponding field; an unspecified value is returned. It is an error to
    402 pass a modifier a first argument which is not a record of the appropriate
    403 type.
    404 
    405 @end itemize
    406 
    407 For instance, the following record-type definition
    408 
    409 @lisp
    410 (define-record-type @svar{pare}
    411   (kons x y)
    412   pare?
    413   (x kar set-kar!)
    414   (y kdr))
    415 @end lisp
    416 
    417 defines @code{kons} to be a constructor, @code{kar} and @code{kdr}
    418 to be accessors, @code{set-kar!} to be a modifier, and @code{pare?}
    419 to be a predicate for instances of @code{<pare>}.
    420 
    421 @lisp
    422 (pare? (kons 1 2))        @result{} #t
    423   (pare? (cons 1 2))        @result{} #f
    424   (kar (kons 1 2))          @result{} 1
    425   (kdr (kons 1 2))          @result{} 2
    426   (let ((k (kons 1 2)))
    427     (set-kar! k 3)
    428     (kar k))                @result{} 3
    429 @end lisp
    430 
    431 @end deffn
    432 
    433 @node Libraries
    434 @section Libraries
    435 
    436 Libraries provide a way to organize Scheme programs into reusable parts
    437 with explicitly defined interfaces to the rest of the program. This
    438 section defines the notation and semantics for libraries.
    439 
    440 @menu
    441 * Library syntax::
    442 * Library example::
    443 @end menu
    444 
    445 @node Library syntax
    446 @subsection Library syntax
    447 
    448 A library definition takes the following form:
    449 
    450 @display
    451 @code{(define-library }@svar{library name}
    452   @svar{library declaration} @dots{}@code{)}
    453 @end display
    454 
    455 @svar{library name} is a list whose members are identifiers and exact
    456 non-negative integers. It is used to identify the library uniquely when
    457 importing from other programs or libraries. Libraries whose first
    458 identifier is @code{scheme} are reserved for use by this report and future
    459 versions of this report. Libraries whose first identifier is @code{srfi}
    460 are reserved for libraries implementing Scheme Requests for
    461 Implementation. It is inadvisable, but not an error, for identifiers in
    462 library names to contain any of the characters @code{| \ ? * < " : > +
    463 [ ] /} or control characters after escapes are expanded.
    464 
    465 A @svar{library declaration} is any of:
    466 
    467 @itemize
    468 
    469 @item
    470 @code{(export }@svar{export spec} @dots{}@code{)}
    471 
    472 @item
    473 @code{(import }@svar{import set} @dots{}@code{)}
    474 
    475 @item
    476 @code{(begin }@svar{command or definition} @dots{}@code{)}
    477 
    478 @item
    479 @code{(include }@svar{filename@sub{1}} @svar{filename@sub{2}}
    480 @dots{}@code{)}
    481 
    482 @item
    483 @code{(include-ci }@svar{filename@sub{1}} @svar{filename@sub{2}}
    484 @dots{}@code{)}
    485 
    486 @item
    487 @code{(include-library-declarations }@svar{filename@sub{1}}
    488 @svar{filename@sub{2}} @dots{}@code{)}
    489 
    490 @item
    491 @code{(cond-expand }@svar{ce-clause@sub{1}} @svar{ce-clause@sub{2}}
    492 @dots{}@code{)}
    493 
    494 @end itemize
    495 
    496 An @code{export} declaration specifies a list of identifiers which can be
    497 made visible to other libraries or programs. An @svar{export spec} takes
    498 one of the following forms:
    499 
    500 @itemize
    501 
    502 @item
    503 @svar{identifier}
    504 
    505 @item
    506 @code{(rename }@svar{identifier@sub{1}} @svar{identifier@sub{2}}@code{)}
    507 
    508 @end itemize
    509 
    510 In an @svar{export spec}, an @svar{identifier} names a single binding
    511 defined within or imported into the library, where the external name
    512 for the export is the same as the name of the binding within the
    513 library. A @code{rename} spec exports the binding defined within
    514 or imported into the library and named by @svar{identifier@sub{1}}
    515 in each (@svar{identifier@sub{1}} @svar{identifier@sub{2}}) pairing,
    516 using @svar{identifier@sub{2}} as the external name.
    517 
    518 An @code{import} declaration provides a way to import the identifiers
    519 exported by another library. It has the same syntax and semantics as
    520 an import declaration used in a program or at the REPL (see @ref{Import
    521 declarations}).
    522 
    523 The @code{begin}, @code{include}, and @code{include-ci} declarations
    524 are used to specify the body of the library. They have the same syntax
    525 and semantics as the corresponding expression types. This form of
    526 @code{begin} is analogous to, but not the same as, the two types of
    527 @code{begin} defined in @ref{Sequencing}.
    528 
    529 The @code{include-library-declarations} declaration is similar to
    530 @code{include} except that the contents of the file are spliced directly
    531 into the current library definition. This can be used, for example, to
    532 share the same @code{export} declaration among multiple libraries as a
    533 simple form of library interface.
    534 
    535 The @code{cond-expand} declaration has the same syntax and semantics
    536 as the @code{cond-expand} expression type, except that it expands to
    537 spliced-in library declarations rather than expressions enclosed in
    538 @code{begin}.
    539 
    540 One possible implementation of libraries is as follows: After all
    541 @code{cond-expand} library declarations are expanded, a new environment
    542 is constructed for the library consisting of all imported bindings. The
    543 expressions from all @code{begin}, @code{include} and @code{include-ci}
    544 library declarations are expanded in that environment in the order in
    545 which they occur in the library. Alternatively, @code{cond-expand}
    546 and @code{import} declarations may be processed in left to right
    547 order interspersed with the processing of other declarations, with
    548 the environment growing as imported bindings are added to it by each
    549 @code{import} declaration.
    550 
    551 When a library is loaded, its expressions are executed in textual order.
    552 If a library's definitions are referenced in the expanded form of
    553 a program or library body, then that library must be loaded before
    554 the expanded program or library body is evaluated. This rule applies
    555 transitively. If a library is imported by more than one program or
    556 library, it may possibly be loaded additional times.
    557 
    558 Similarly, during the expansion of a library @code{(foo)}, if any syntax
    559 keywords imported from another library @code{(bar)} are needed to expand
    560 the library, then the library @code{(bar)} must be expanded and its
    561 syntax definitions evaluated before the expansion of @code{(foo)}.
    562 
    563 Regardless of the number of times that a library is loaded, each program
    564 or library that imports bindings from a library must do so from a single
    565 loading of that library, regardless of the number of import declarations
    566 in which it appears. That is, @code{(import (only (foo) a))} followed
    567 by @code{(import (only (foo) b))} has the same effect as @code{(import
    568 (only (foo) a b))}.
    569 
    570 @node Library example
    571 @subsection Library example
    572 
    573 The following example shows how a program can be divided into libraries
    574 plus a relatively small main program [@ref{life}]. If the main program is entered
    575 into a REPL, it is not necessary to import the base library.
    576 
    577 @lisp
    578 (define-library (example grid)
    579   (export make rows cols ref each
    580           (rename put! set!))
    581   (import (scheme base))
    582   (begin
    583     ;; Create an NxM grid.
    584     (define (make n m)
    585       (let ((grid (make-vector n)))
    586         (do ((i 0 (+ i 1)))
    587             ((= i n) grid)
    588           (let ((v (make-vector m #false)))
    589             (vector-set! grid i v)))))
    590     (define (rows grid)
    591       (vector-length grid))
    592     (define (cols grid)
    593       (vector-length (vector-ref grid 0)))
    594     ;; Return #false if out of range.
    595     (define (ref grid n m)
    596       (and (< -1 n (rows grid))
    597            (< -1 m (cols grid))
    598            (vector-ref (vector-ref grid n) m)))
    599     (define (put! grid n m v)
    600       (vector-set! (vector-ref grid n) m v))
    601     (define (each grid proc)
    602       (do ((j 0 (+ j 1)))
    603           ((= j (rows grid)))
    604         (do ((k 0 (+ k 1)))
    605             ((= k (cols grid)))
    606           (proc j k (ref grid j k)))))))
    607 
    608 (define-library (example life)
    609   (export life)
    610   (import (except (scheme base) set!)
    611           (scheme write)
    612           (example grid))
    613   (begin
    614     (define (life-count grid i j)
    615       (define (count i j)
    616         (if (ref grid i j) 1 0))
    617       (+ (count (- i 1) (- j 1))
    618          (count (- i 1) j)
    619          (count (- i 1) (+ j 1))
    620          (count i (- j 1))
    621          (count i (+ j 1))
    622          (count (+ i 1) (- j 1))
    623          (count (+ i 1) j)
    624          (count (+ i 1) (+ j 1))))
    625     (define (life-alive? grid i j)
    626       (case (life-count grid i j)
    627         ((3) #true)
    628         ((2) (ref grid i j))
    629         (else #false)))
    630     (define (life-print grid)
    631       (display "\x1B;[1H\x1B;[J")  ; clear vt100
    632       (each grid
    633             (lambda (i j v)
    634               (display (if v "*" " "))
    635               (when (= j (- (cols grid) 1))
    636                 (newline)))))
    637     (define (life grid iterations)
    638       (do ((i 0 (+ i 1))
    639            (grid0 grid grid1)
    640            (grid1 (make (rows grid) (cols grid))
    641                   grid0))
    642           ((= i iterations))
    643         (each grid0
    644               (lambda (j k v)
    645                 (let ((a (life-alive? grid0 j k)))
    646                   (set! grid1 j k a))))
    647         (life-print grid1)))))))
    648 
    649 ;; Main program.
    650 (import (scheme base)
    651         (only (example life) life)
    652         (rename (prefix (example grid) grid-)
    653                 (grid-make make-grid)))
    654 
    655 ;; Initialize a grid with a glider.
    656 (define grid (make-grid 24 24))
    657 (grid-set! grid 1 1 #true)
    658 (grid-set! grid 2 2 #true)
    659 (grid-set! grid 3 0 #true)
    660 (grid-set! grid 3 1 #true)
    661 (grid-set! grid 3 2 #true)
    662 
    663 ;; Run for 80 iterations.
    664 (life grid 80)
    665 @end lisp
    666 
    667 @node The REPL
    668 @section The REPL
    669 
    670 Implementations may provide an interactive session called a @define{REPL}
    671 (Read-Eval-Print Loop), where import declarations, expressions and
    672 definitions can be entered and evaluated one at a time. For convenience
    673 and ease of use, the global Scheme environment in a REPL must not be
    674 empty, but must start out with at least the bindings provided by the base
    675 library. This library includes the core syntax of Scheme and generally
    676 useful procedures that manipulate data. For example, the variable
    677 @code{abs} is bound to a procedure of one argument that computes the
    678 absolute value of a number, and the variable @code{+} is bound to a
    679 procedure that computes sums. The full list of @code{(scheme base)}
    680 bindings can be found in @ref{Appendix A}.
    681 
    682 Implementations may provide an initial REPL environment which behaves as
    683 if all possible variables are bound to locations, most of which contain
    684 unspecified values. Top level REPL definitions in such an implementation
    685 are truly equivalent to assignments, unless the identifier is defined
    686 as a syntax keyword.
    687 
    688 An implementation may provide a mode of operation in which the REPL
    689 reads its input from a file. Such a file is not, in general, the same
    690 as a program, because it can contain import declarations in places other
    691 than the beginning.